SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/read_nam_grid_conf_proj.F90
Go to the documentation of this file.
00001 !     ################################################################
00002       SUBROUTINE READ_NAM_GRID_CONF_PROJ(HPROGRAM,KGRID_PAR,KL,PGRID_PAR)
00003 !     ################################################################
00004 !
00005 !!****  *READ_NAM_GRID_CONF_PROJ* - routine to read in namelist the horizontal grid
00006 !!
00007 !!    PURPOSE
00008 !!    -------
00009 !!
00010 !!**  METHOD
00011 !!    ------
00012 !!
00013 !!    EXTERNAL
00014 !!    --------
00015 !!
00016 !!
00017 !!    IMPLICIT ARGUMENTS
00018 !!    ------------------
00019 !!
00020 !!    REFERENCE
00021 !!    ---------
00022 !!
00023 !!
00024 !!    AUTHOR
00025 !!    ------
00026 !!      V. Masson   *Meteo France*      
00027 !!
00028 !!    MODIFICATIONS
00029 !!    -------------
00030 !!      Original    01/2004 
00031 !!      A.Alias    10/2010 - XLATC/XLONC added to save the XLATCEN/XLONCEN values for FA
00032 !-------------------------------------------------------------------------------
00033 !
00034 !*       0.    DECLARATIONS
00035 !              ------------
00036 !
00037 USE MODE_POS_SURF
00038 !
00039 USE MODI_OPEN_NAMELIST
00040 USE MODI_CLOSE_NAMELIST
00041 USE MODI_GET_LUOUT
00042 !
00043 USE MODE_GRIDTYPE_CONF_PROJ
00044 USE MODD_GRID_CONF_PROJ, ONLY : XLATC, XLONC
00045 !
00046 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00047 USE PARKIND1  ,ONLY : JPRB
00048 !
00049 IMPLICIT NONE
00050 !
00051 !*       0.1   Declarations of arguments
00052 !              -------------------------
00053 !
00054  CHARACTER(LEN=6),           INTENT(IN)    :: HPROGRAM   ! calling program
00055 INTEGER,                    INTENT(INOUT) :: KGRID_PAR  ! size of PGRID_PAR
00056 INTEGER,                    INTENT(OUT)   :: KL         ! number of points
00057 REAL, DIMENSION(KGRID_PAR), INTENT(OUT)   :: PGRID_PAR  ! parameters defining this grid
00058 !
00059 !*       0.2   Declarations of local variables
00060 !              -------------------------------
00061 !
00062 INTEGER :: ILUOUT ! output listing logical unit
00063 INTEGER :: ILUNAM ! namelist file  logical unit
00064 INTEGER :: JI, JJ ! loop counters
00065 INTEGER :: JL     ! loop counter
00066 
00067 REAL, DIMENSION(:),   ALLOCATABLE :: ZX       ! X conformal coordinate of grid mesh
00068 REAL, DIMENSION(:),   ALLOCATABLE :: ZY       ! Y conformal coordinate of grid mesh
00069 REAL, DIMENSION(:),   ALLOCATABLE :: ZDX      ! X grid mesh size
00070 REAL, DIMENSION(:),   ALLOCATABLE :: ZDY      ! Y grid mesh size
00071 REAL, DIMENSION(1)                :: ZXOR     ! X conformal coordinate of origine point
00072 REAL, DIMENSION(1)                :: ZYOR     ! Y conformal coordinate of origin point
00073 REAL, DIMENSION(1)                :: ZLATOR   ! latitude of origine point
00074 REAL, DIMENSION(1)                :: ZLONOR   ! longitude of origin point
00075 !
00076 !*       0.3   Declarations of namelist
00077 !              ------------------------
00078 !
00079 REAL    :: XLAT0    ! reference latitude
00080 REAL    :: XLON0    ! reference longitude
00081 REAL    :: XRPK     ! projection parameter 
00082 !                   !   K=1 : stereographic north pole
00083 !                   ! 0<K<1 : Lambert, north hemisphere
00084 !                   !   K=0 : Mercator
00085 !                   !-1<K<0 : Lambert, south hemisphere
00086 !                   !   K=-1: stereographic south pole
00087 REAL    :: XBETA    ! angle between grid and reference longitude
00088 REAL    :: XLATCEN  ! latitude  of center point
00089 REAL    :: XLONCEN  ! longitude of center point
00090 INTEGER :: NIMAX    ! number of points in I direction
00091 INTEGER :: NJMAX    ! number of points in J direction
00092 REAL    :: XDX      ! increment in X direction (in meters)
00093 REAL    :: XDY      ! increment in Y direction (in meters)
00094 !
00095 REAL, DIMENSION(:), POINTER :: ZGRID_PAR
00096 !
00097 LOGICAL :: GFOUND
00098 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00099 !
00100 NAMELIST/NAM_CONF_PROJ/XLAT0, XLON0, XRPK, XBETA
00101 NAMELIST/NAM_CONF_PROJ_GRID/NIMAX,NJMAX,XLATCEN,XLONCEN,XDX,XDY
00102 !
00103 !------------------------------------------------------------------------------
00104 !
00105 !*       1.    opening of namelist
00106 ! 
00107 IF (LHOOK) CALL DR_HOOK('READ_NAM_GRID_CONF_PROJ',0,ZHOOK_HANDLE)
00108  CALL GET_LUOUT(HPROGRAM,ILUOUT)
00109 !
00110  CALL OPEN_NAMELIST(HPROGRAM,ILUNAM)
00111 !
00112 !---------------------------------------------------------------------------
00113 !
00114 !*       2.    Reading of projection parameters
00115 !              --------------------------------
00116 !
00117  CALL POSNAM(ILUNAM,'NAM_CONF_PROJ',GFOUND,ILUOUT)
00118 IF (GFOUND) READ(UNIT=ILUNAM,NML=NAM_CONF_PROJ)
00119 !
00120 !---------------------------------------------------------------------------
00121 !
00122 !*       2.    Reading parameters of the grid
00123 !              ------------------------------
00124 !
00125  CALL POSNAM(ILUNAM,'NAM_CONF_PROJ_GRID',GFOUND,ILUOUT)
00126 IF (GFOUND) READ(UNIT=ILUNAM,NML=NAM_CONF_PROJ_GRID)
00127 !
00128 !---------------------------------------------------------------------------
00129  CALL CLOSE_NAMELIST(HPROGRAM,ILUNAM)
00130 !---------------------------------------------------------------------------
00131 !
00132 !*       3.    Number of points
00133 !              ----------------
00134 !
00135 KL = NIMAX * NJMAX
00136 !
00137 !---------------------------------------------------------------------------
00138 !
00139 !*       3.    Array of X and Y coordinates
00140 !              ----------------------------
00141 !
00142 !
00143 ALLOCATE(ZX(KL))
00144 ALLOCATE(ZY(KL))
00145 DO JJ=1,NJMAX
00146   DO JI=1,NIMAX
00147     JL = JI + (JJ-1) * NIMAX
00148     ZX(JL) = FLOAT(JI) * XDX
00149     ZY(JL) = FLOAT(JJ) * XDY
00150   END DO
00151 END DO
00152 !
00153 !---------------------------------------------------------------------------
00154 !
00155 !*       4.    Array of X and Y increments
00156 !              ---------------------------
00157 !
00158 ALLOCATE(ZDX(KL))
00159 ALLOCATE(ZDY(KL))
00160 ZDX(:) = XDX
00161 ZDY(:) = XDY
00162 !
00163 !---------------------------------------------------------------------------
00164 !
00165 !*       5.    Latitude and longitude of point of coordinates 0,0
00166 !              --------------------------------------------------
00167 !
00168 ! Coordinates of origin point are here defined from center point, that
00169 ! is then used as substitute reference point.
00170 ! In all further computations, origin point will be of course be x=0, y=0
00171 !
00172 ZXOR = - FLOAT(NIMAX+1)/2.*XDX
00173 ZYOR = - FLOAT(NJMAX+1)/2.*XDY
00174 !
00175  CALL LATLON_CONF_PROJ(XLAT0,XLON0,XRPK,XBETA,XLATCEN,XLONCEN, &
00176                         ZXOR,ZYOR,ZLATOR,ZLONOR                 )  
00177 !
00178 XLATC=XLATCEN
00179 XLONC=XLONCEN
00180 !---------------------------------------------------------------------------
00181 !
00182 !*       8.    All this information stored into pointer PGRID_PAR
00183 !              --------------------------------------------------
00184 !
00185  CALL PUT_GRIDTYPE_CONF_PROJ(ZGRID_PAR,XLAT0,XLON0,XRPK,XBETA,    &
00186                               ZLATOR(1),ZLONOR(1),NIMAX,NJMAX,     &
00187                               ZX,ZY,ZDX,ZDY                        )  
00188 !
00189 !---------------------------------------------------------------------------
00190 DEALLOCATE(ZX)
00191 DEALLOCATE(ZY)
00192 DEALLOCATE(ZDX)
00193 DEALLOCATE(ZDY)
00194 !---------------------------------------------------------------------------
00195 !
00196 !* 1st call : initializes dimension
00197 !
00198 IF (KGRID_PAR==0) THEN
00199   KGRID_PAR = SIZE(ZGRID_PAR)
00200 !
00201 ELSE
00202 !
00203 !* 2nd call : initializes grid array
00204 !
00205   PGRID_PAR(:) = 0.
00206   PGRID_PAR(:) = ZGRID_PAR
00207 END IF
00208 !
00209 DEALLOCATE(ZGRID_PAR)
00210 IF (LHOOK) CALL DR_HOOK('READ_NAM_GRID_CONF_PROJ',1,ZHOOK_HANDLE)
00211 !
00212 !---------------------------------------------------------------------------
00213 !
00214 END SUBROUTINE READ_NAM_GRID_CONF_PROJ