GRID_t Derived Type

type, public :: GRID_t


Contents

Source Code


Components

TypeVisibility AttributesNameInitial
integer, public :: NDIM
character(len=10), public :: CGRID
integer, public :: NGRID_PAR
real, public, POINTER, DIMENSION(:):: XGRID_PAR
real, public, POINTER, DIMENSION(:):: XLAT
real, public, POINTER, DIMENSION(:):: XLON
real, public, POINTER, DIMENSION(:):: XMESH_SIZE

Source Code

TYPE GRID_t
!-------------------------------------------------------------------------------
!
! Grid definition
!
  INTEGER                         :: NDIM        ! number of points
  CHARACTER(LEN=10)               :: CGRID       ! grid type
!                                              ! "NONE        " : no grid computations
!                                              ! "CONF PROJ   " : conformal projection
!                                              ! "SURF ATM    " : nature points of surf. atm. grid
!
  INTEGER                         :: NGRID_PAR   ! size of XGRID_PAR
  REAL, POINTER,     DIMENSION(:) :: XGRID_PAR   ! lits of parameters used to define the grid
!                                              ! (depends on value of CGRID)
!
!-------------------------------------------------------------------------------
!
! General surface parameters:
!
  REAL, POINTER, DIMENSION(:) :: XLAT        ! latitude (degrees +North)               (-)
  REAL, POINTER, DIMENSION(:) :: XLON        ! longitude (degrees +East)               (-)
  REAL, POINTER, DIMENSION(:) :: XMESH_SIZE  ! mesh size                               (m2)
!-------------------------------------------------------------------------------
!
END TYPE GRID_t