ResampleFloat Subroutine

private subroutine ResampleFloat(grid, resampledGrid)

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: grid
type(grid_real), intent(inout) :: resampledGrid

Variables

Type Visibility Attributes Name Initial
logical, public :: check
integer, public :: i
integer, public :: iold
integer, public :: j
integer, public :: jold
real, public :: x
real, public :: y

Source Code

SUBROUTINE ResampleFloat &
!
(grid, resampledGrid)


IMPLICIT NONE

! Arguments with intent(in):
TYPE (grid_real), INTENT(IN) :: grid

!Arguments with intent(inout):
TYPE (grid_real), INTENT(INOUT) :: resampledGrid

!Local declarations:
REAL :: x, y
INTEGER :: i, j, iold, jold
LOGICAL :: check
!---------------------------end of declarations--------------------------------

!check that input and output grid have the same coordinate reference system
IF ( .NOT. grid % grid_mapping == resampledGrid % grid_mapping) THEN
  CALL Catch ('error', 'GridOperations',  &
     'coordinate reference system of resampled grid differs from input grid' )
END IF 


!fill in resampled grid. Skip nodata
DO i = 1, resampledGrid % idim
  DO j = 1, resampledGrid % jdim
    IF (resampledGrid % mat (i,j) /= resampledGrid % nodata) THEN
      CALL GetXY (i, j, resampledGrid, x, y)
      CALL GetIJ (x, y, grid, iold, jold, check)
      IF (check) THEN
           resampledGrid % mat (i,j) = grid % mat (iold, jold)
      ELSE
           resampledGrid % mat (i,j) = resampledGrid % nodata
      END IF
    END IF
  END DO
END DO

END SUBROUTINE ResampleFloat