UNGRIDB() and UNGRIDI()

Fortran version:

For I/O API Version 3.2: UNGRIDB() and UNGRIDI() are Fortran-90 generic routines with optionally 1-D or 2-D REAL or REAL*8 location-arguments, with INTERFACEs defined in MODULE M3UTILIO.
12/1/2017: Added forms with IERR argument for I/O API 3.2:

For previous I/O API versions, UNGRIDB() and UNGRIDB() have the same argument list as I/O API Version 3.2 single-indexed REAL forms, but do not have INTERFACEs (hence Fortran-77 style argument behavior).

    SUBROUTINE UNGRIDB( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NPTS2, XLOCR, YLOCR, NU1, CU1 )
    SUBROUTINE UNGRIDB( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NPTS2, XLOCD, YLOCD, NU1, CU1 )
    SUBROUTINE UNGRIDB( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NCOL2, NROW2, XGRDR, YGRDR, NU2, CU2 )
    SUBROUTINE UNGRIDB( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NCOL2, NROW2, XGRDD, YGRDD, NU2, CU2 )
    SUBROUTINE UNGRIDB( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NPTS2, XLOCR, YLOCR, NU1, CU1, IERR )
    SUBROUTINE UNGRIDB( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NPTS2, XLOCD, YLOCD, NU1, CU1, IERR )
    SUBROUTINE UNGRIDB( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NCOL2, NROW2, XGRDR, YGRDR, NU2, CU2, IERR )
    SUBROUTINE UNGRIDB( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NCOL2, NROW2, XGRDD, YGRDD, NU2, CU2, IERR )

    SUBROUTINE UNGRIDI( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NPTS2, XLOCR, YLOCR, NX1 )
    SUBROUTINE UNGRIDI( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NPTS2, XLOCD, YLOCD, NX1 )
    SUBROUTINE UNGRIDI( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NCOL2, NROW2, XGRDR, YGRDR, NX2 )
    SUBROUTINE UNGRIDI( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NCOL2, NROW2, XGRDD, YGRDD, NX2 )
    SUBROUTINE UNGRIDI( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NPTS2, XLOCR, YLOCR, NX1, IERR )
    SUBROUTINE UNGRIDI( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NPTS2, XLOCD, YLOCD, NX1, IERR )
    SUBROUTINE UNGRIDI( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NCOL2, NROW2, XGRDR, YGRDR, NX2, IERR )
    SUBROUTINE UNGRIDI( NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL,   &
                        NCOL2, NROW2, XGRDD, YGRDD, NX2, IERR )

        INTEGER, INTENT(IN   ) :: NCOL1, NROW1
        REAL*8 , INTENT(IN   ) :: XORIG, YORIG, XCELL, YCELL
        INTEGER, INTENT(IN   ) :: NPTS2, NCOL2, NROW2
        REAL   , INTENT(IN   ) :: XLOCR( NPTS2 ),       YLOCR( NPTS2 )
        REAL   , INTENT(IN   ) :: XGRDR( NCOL1,NROW1 ), YGRDR( NCOL1,NROW1 )
        REAL*8 , INTENT(IN   ) :: XLOCD( NPTS ),        YLOCD( NPTS2 )
        REAL*8 , INTENT(IN   ) :: XGRDD( NCOL1,NROW1 ), YGRDD( NCOL1,NROW1 )
        INTEGER, INTENT(  OUT) :: NU1( 4,NPTS2 )
        INTEGER, INTENT(  OUT) :: NU2( 4,NCOL2,NROW2 )
        INTEGER, INTENT(  OUT) :: NX1( 4,NPTS2 )
        INTEGER, INTENT(  OUT) :: NX2( 4,NCOL2,NROW2 )
        REAL   , INTENT(  OUT) :: CU1( 4,NPTS2 )
        REAL   , INTENT(  OUT) :: CU2( 4,NCOL2,NROW2 )
        INTEGER, INTENT(  OUT) :: IERR

        !!  NCOL1, NROW1, XORIG, YORIG, XCELL, YCELL are defining
        !!  parameters for the output-grid for the matrix-transform;
        !!  NPTS2, NCOL2, NROW2, XLOC*, YLOC*, XGRD* amd YGRD* are
        !!  the dimensions and locations for the input-data for 
        !!  the matrix transform.
        !!  NU*, CU* are the indexes and coefficients for the bilinear
        !!  interpolation matrix
        !!  NX* are the indexes for the incidence matrix.
        !!  IERR counts out-of-grid errors; IERR=0 means no errors.
        

C version: none

Summary:

For I/O API Version 3.2 and later, generic versions of these routines are declared in MODULE M3UTILIO, for which the input arguments XLOC and YLOC are either 1-D or 2D, and are either REAL or REAL*8. Routines UNGRIDBS1() and UNGRIDIS1() (which have 1-D single-precision location-arguments) correspond to the routines from I/O API Version 3.1 and earlier.

UNGRIDB() computes "ungridding" matrices used by subroutines BMATVEC() and BILIN() to perform bilinear interpolation from a grid to a set of target (e.g., point source) locations or a grid

{ <XLOC(S),YLOC(S)>: S=1,NPTS2 } { <XGRD(C,R),YGRD(C,R)>: C=1,NCOL2, R=1,NROW2 }
, after the form (simplest case: non-layered set of points as interpolation-target), so that for a variable V1(NCOLS*NROWS) single-indexed on the source grid, the value at<XLOC(S),YLOC(S)> is given by the formula
VNEW(S) = SUMJ = 1...4 [ CU(J,S) V1( NU(J,S) ) ]
More detail on the computation of these coefficients, etc., is given in the section on BMATVEC().

UNGRIDI() computes "incidence matrix ungridding" indices for grid-to-grid transformation from a grid to the set of target (e.g., point source) locations or a new grid, as specified above, i.e., so that for a variable V1(NCOLS*NROWS) single-indexed on the source grid,

VNEW(S) = V1(NX(S)) is the value at <XLOC(S),YLOC(S)>

Note that for the versions without the IERR argument, it is the responsibility of the caller to ensure that the points <XLOC,YLOC> or <XGRD,YLGRD> are inside the grid; otherwise, it is the responsibility of the caller to check IERR and respond accordingly.
If the points are not inside the grid, the code will make a "best effort" using "extend-by-constant" on the boundaries.

See also subroutines

GCTP coordinate transformation routine from USGS

GRID2XY(): Grid-cell-center coordinate transformation routinee in MODULE MODGCTP

GRID2INDX(), PNTS2INDX(), and INDXMULT() "New" bilinear interpolation package from MODULE MODGCTP

BMATVEC() and BILIN(), DMATVE()C, PMATVE()C, and SMATVEC()

and programs
mtxblend, mtxbuild, mtxcalc, mtxcple.

Fortran Usage:

For Fortran-90 declarations and interface checking:
    USE M3UTILIO
    

See usage guide under BMATVEC()


Previous: SETSPHERE and SPHEREDAT

Previous: TRIMLEN

Next: UPCASE

Up: Coordinate and Grid Related Routines

Up: Utility Routines

To: Models-3/EDSS I/O API: The Help Pages