SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_nam_grid_conf_proj.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! ################################################################
6  SUBROUTINE read_nam_grid_conf_proj(HPROGRAM,KGRID_PAR,KL,PGRID_PAR)
7 ! ################################################################
8 !
9 !!**** *READ_NAM_GRID_CONF_PROJ* - routine to read in namelist the horizontal grid
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !!
28 !! AUTHOR
29 !! ------
30 !! V. Masson *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 01/2004
35 !! A.Alias 10/2010 - XLATC/XLONC added to save the XLATCEN/XLONCEN values for FA
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 USE mode_pos_surf
42 !
43 USE modi_open_namelist
44 USE modi_close_namelist
45 USE modi_get_luout
46 !
48 USE modd_grid_conf_proj, ONLY : xlatc, xlonc
49 !
50 USE yomhook ,ONLY : lhook, dr_hook
51 USE parkind1 ,ONLY : jprb
52 !
53 IMPLICIT NONE
54 !
55 !* 0.1 Declarations of arguments
56 ! -------------------------
57 !
58  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
59 INTEGER, INTENT(INOUT) :: kgrid_par ! size of PGRID_PAR
60 INTEGER, INTENT(OUT) :: kl ! number of points
61 REAL, DIMENSION(KGRID_PAR), INTENT(OUT) :: pgrid_par ! parameters defining this grid
62 !
63 !* 0.2 Declarations of local variables
64 ! -------------------------------
65 !
66 INTEGER :: iluout ! output listing logical unit
67 INTEGER :: ilunam ! namelist file logical unit
68 INTEGER :: ji, jj ! loop counters
69 INTEGER :: jl ! loop counter
70 
71 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X conformal coordinate of grid mesh
72 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y conformal coordinate of grid mesh
73 REAL, DIMENSION(:), ALLOCATABLE :: zdx ! X grid mesh size
74 REAL, DIMENSION(:), ALLOCATABLE :: zdy ! Y grid mesh size
75 REAL, DIMENSION(1) :: zxor ! X conformal coordinate of origine point
76 REAL, DIMENSION(1) :: zyor ! Y conformal coordinate of origin point
77 REAL, DIMENSION(1) :: zlator ! latitude of origine point
78 REAL, DIMENSION(1) :: zlonor ! longitude of origin point
79 !
80 !* 0.3 Declarations of namelist
81 ! ------------------------
82 !
83 REAL :: xlat0 ! reference latitude
84 REAL :: xlon0 ! reference longitude
85 REAL :: xrpk ! projection parameter
86 ! ! K=1 : stereographic north pole
87 ! ! 0<K<1 : Lambert, north hemisphere
88 ! ! K=0 : Mercator
89 ! !-1<K<0 : Lambert, south hemisphere
90 ! ! K=-1: stereographic south pole
91 REAL :: xbeta ! angle between grid and reference longitude
92 REAL :: xlatcen ! latitude of center point
93 REAL :: xloncen ! longitude of center point
94 INTEGER :: nimax ! number of points in I direction
95 INTEGER :: njmax ! number of points in J direction
96 REAL :: xdx ! increment in X direction (in meters)
97 REAL :: xdy ! increment in Y direction (in meters)
98 !
99 REAL, DIMENSION(:), POINTER :: zgrid_par
100 !
101 LOGICAL :: gfound
102 REAL(KIND=JPRB) :: zhook_handle
103 !
104 namelist/nam_conf_proj/xlat0, xlon0, xrpk, xbeta
105 namelist/nam_conf_proj_grid/nimax,njmax,xlatcen,xloncen,xdx,xdy
106 !
107 !------------------------------------------------------------------------------
108 !
109 !* 1. opening of namelist
110 !
111 IF (lhook) CALL dr_hook('READ_NAM_GRID_CONF_PROJ',0,zhook_handle)
112  CALL get_luout(hprogram,iluout)
113 !
114  CALL open_namelist(hprogram,ilunam)
115 !
116 !---------------------------------------------------------------------------
117 !
118 !* 2. Reading of projection parameters
119 ! --------------------------------
120 !
121  CALL posnam(ilunam,'NAM_CONF_PROJ',gfound,iluout)
122 IF (gfound) READ(unit=ilunam,nml=nam_conf_proj)
123 !
124 !---------------------------------------------------------------------------
125 !
126 !* 2. Reading parameters of the grid
127 ! ------------------------------
128 !
129  CALL posnam(ilunam,'NAM_CONF_PROJ_GRID',gfound,iluout)
130 IF (gfound) READ(unit=ilunam,nml=nam_conf_proj_grid)
131 !
132 !---------------------------------------------------------------------------
133  CALL close_namelist(hprogram,ilunam)
134 !---------------------------------------------------------------------------
135 !
136 !* 3. Number of points
137 ! ----------------
138 !
139 kl = nimax * njmax
140 !
141 !---------------------------------------------------------------------------
142 !
143 !* 3. Array of X and Y coordinates
144 ! ----------------------------
145 !
146 !
147 ALLOCATE(zx(kl))
148 ALLOCATE(zy(kl))
149 DO jj=1,njmax
150  DO ji=1,nimax
151  jl = ji + (jj-1) * nimax
152  zx(jl) = float(ji) * xdx
153  zy(jl) = float(jj) * xdy
154  END DO
155 END DO
156 !
157 !---------------------------------------------------------------------------
158 !
159 !* 4. Array of X and Y increments
160 ! ---------------------------
161 !
162 ALLOCATE(zdx(kl))
163 ALLOCATE(zdy(kl))
164 zdx(:) = xdx
165 zdy(:) = xdy
166 !
167 !---------------------------------------------------------------------------
168 !
169 !* 5. Latitude and longitude of point of coordinates 0,0
170 ! --------------------------------------------------
171 !
172 ! Coordinates of origin point are here defined from center point, that
173 ! is then used as substitute reference point.
174 ! In all further computations, origin point will be of course be x=0, y=0
175 !
176 zxor = - float(nimax+1)/2.*xdx
177 zyor = - float(njmax+1)/2.*xdy
178 !
179  CALL latlon_conf_proj(xlat0,xlon0,xrpk,xbeta,xlatcen,xloncen, &
180  zxor,zyor,zlator,zlonor )
181 !
182 xlatc=xlatcen
183 xlonc=xloncen
184 !---------------------------------------------------------------------------
185 !
186 !* 8. All this information stored into pointer PGRID_PAR
187 ! --------------------------------------------------
188 !
189  CALL put_gridtype_conf_proj(zgrid_par,xlat0,xlon0,xrpk,xbeta, &
190  zlator(1),zlonor(1),nimax,njmax, &
191  zx,zy,zdx,zdy )
192 !
193 !---------------------------------------------------------------------------
194 DEALLOCATE(zx)
195 DEALLOCATE(zy)
196 DEALLOCATE(zdx)
197 DEALLOCATE(zdy)
198 !---------------------------------------------------------------------------
199 !
200 !* 1st call : initializes dimension
201 !
202 IF (kgrid_par==0) THEN
203  kgrid_par = SIZE(zgrid_par)
204 !
205 ELSE
206 !
207 !* 2nd call : initializes grid array
208 !
209  pgrid_par(:) = 0.
210  pgrid_par(:) = zgrid_par
211 END IF
212 !
213 DEALLOCATE(zgrid_par)
214 IF (lhook) CALL dr_hook('READ_NAM_GRID_CONF_PROJ',1,zhook_handle)
215 !
216 !---------------------------------------------------------------------------
217 !
218 END SUBROUTINE read_nam_grid_conf_proj
subroutine put_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, KIMAX, KJMAX, PX, PY, PDX, PDY)
subroutine latlon_conf_proj(PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, PX, PY, PLAT, PLON)
subroutine read_nam_grid_conf_proj(HPROGRAM, KGRID_PAR, KL, PGRID_PAR)
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)