SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_nam_grid_ign.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_ign(HPROGRAM,KGRID_PAR,KL,PGRID_PAR)
7 ! ################################################################
8 !
9 !!**** *READ_NAM_GRID_IGN* - 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 !! E. Martin *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 10/2007
35 !! 07/2011 add maximum domain dimension for output (B. Decharme)
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 USE modd_surf_par, ONLY : xundef
42 !
43 USE mode_pos_surf
44 !
45 USE modi_open_namelist
46 USE modi_close_namelist
47 USE modi_get_luout
49 !
51 USE modi_get_xyall_ign
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 IMPLICIT NONE
57 !
58 !* 0.1 Declarations of arguments
59 ! -------------------------
60 !
61  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
62 INTEGER, INTENT(INOUT) :: kgrid_par ! size of PGRID_PAR
63 INTEGER, INTENT(OUT) :: kl ! number of points
64 REAL, DIMENSION(KGRID_PAR), INTENT(OUT) :: pgrid_par ! parameters defining this grid
65 !
66 !* 0.2 Declarations of local variables
67 ! -------------------------------
68 !
69 INTEGER :: iluout ! output listing logical unit
70 INTEGER :: ilunam ! namelist file logical unit
71 INTEGER :: ilambert ! Lambert type
72 
73 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X conformal coordinate of grid mesh
74 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y conformal coordinate of grid mesh
75 REAL, DIMENSION(:), ALLOCATABLE :: zdx ! X grid mesh size
76 REAL, DIMENSION(:), ALLOCATABLE :: zdy ! Y grid mesh size
77 !
78 !* 0.3 Declarations of namelist
79 ! ------------------------
80 !
81  CHARACTER(LEN=3) :: clambert ! Lambert type
82 INTEGER :: npoints ! number of points
83 REAL, DIMENSION(100000) :: xx ! X coordinate of grid mesh center (in meters)
84 REAL, DIMENSION(100000) :: xy ! Y coordinate of grid mesh center (in meters)
85 REAL, DIMENSION(100000) :: xdx ! X mesh size (in meters)
86 REAL, DIMENSION(100000) :: xdy ! Y mesh size (in meters)
87 !
88 REAL :: xx_llcorner ! X coordinate of left side of the domain
89 REAL :: xy_llcorner ! Y coordinate of lower side of the domain
90 REAL :: xcellsize ! size of the cell (equal in X and Y)
91 INTEGER :: ncols ! number of columns
92 INTEGER :: nrows ! number of rows
93 !
94 REAL, DIMENSION(:), ALLOCATABLE :: zxall ! maximum domain X coordinate of grid mesh
95 REAL, DIMENSION(:), ALLOCATABLE :: zyall ! maximum domain Y coordinate of grid mesh
96 INTEGER :: idimx ! maximum domain length in X
97 INTEGER :: idimy ! maximum domain length in Y
98 !
99 REAL, DIMENSION(:), POINTER :: zgrid_par
100 !
101 INTEGER :: jcols, jrows, iindex ! loop counters
102 LOGICAL :: gfound
103 REAL(KIND=JPRB) :: zhook_handle
104 !
105 namelist/nam_ign/clambert,npoints,xx,xy,xdx,xdy, &
106  xx_llcorner, xy_llcorner, xcellsize, &
107  ncols, nrows
108 !
109 !------------------------------------------------------------------------------
110 !
111 !* 1. opening of namelist
112 !
113 IF (lhook) CALL dr_hook('READ_NAM_GRID_IGN',0,zhook_handle)
114  CALL get_luout(hprogram,iluout)
115 !
116  CALL open_namelist(hprogram,ilunam)
117 !
118 xx_llcorner = xundef
119 xy_llcorner = xundef
120 xcellsize = xundef
121 ncols = 0
122 nrows = 0
123 !
124 !---------------------------------------------------------------------------
125 !
126 !* 2. Reading of projection parameters
127 ! --------------------------------
128 !
129  CALL posnam(ilunam,'NAM_IGN',gfound,iluout)
130 IF (gfound) READ(unit=ilunam,nml=nam_ign)
131 !
132 !---------------------------------------------------------------------------
133  CALL close_namelist(hprogram,ilunam)
134 !---------------------------------------------------------------------------
135 !
136 !* 3. Initialisation for a regular grid
137 ! ---------------------------------
138 !
139 IF (xcellsize/=xundef) THEN
140  !
141  WRITE(iluout,*) 'Initialisation of IGN Coordinates for a regular grid'
142  !
143  xdx(:) = xcellsize
144  xdy(:) = xcellsize
145  !
146  IF ( xx_llcorner/=xundef .AND. xy_llcorner/=xundef &
147  .AND. ncols>0 .AND. nrows>0 ) THEN
148  !
149  npoints = ncols * nrows
150  !
151  DO jrows=1,nrows
152  DO jcols=1,ncols
153  !
154  iindex = jcols + (jrows-1) * ncols
155  xx(iindex) = xx_llcorner + (jcols-0.5) * xcellsize
156  xy(iindex) = xy_llcorner + (jrows-0.5) * xcellsize
157  !
158  END DO
159  END DO
160  !
161  ENDIF
162  !
163 END IF
164 !
165 !---------------------------------------------------------------------------
166 !
167 !* 3. Number of points
168 ! ----------------
169 !
170 kl = npoints
171 !
172 !---------------------------------------------------------------------------
173 !
174 !* 3. Array of X and Y coordinates
175 ! ----------------------------
176 !
177 !
178 ALLOCATE(zx(kl))
179 ALLOCATE(zy(kl))
180 zx(:) = xx(:kl)
181 zy(:) = xy(:kl)
182 !
183 !---------------------------------------------------------------------------
184 !
185 !* 4. Array of X and Y increments
186 ! ---------------------------
187 !
188 ALLOCATE(zdx(kl))
189 ALLOCATE(zdy(kl))
190 zdx(:) = xdx(:kl)
191 zdy(:) = xdy(:kl)
192 !
193 !---------------------------------------------------------------------------
194 !
195 !* 5. Lambert type
196 ! ------------
197 !
198  CALL test_nam_var_surf(iluout,'CLAMBERT',clambert,'L1 ','L2 ','L3 ',&
199  'L4 ','L2E','L93' )
200 !
201 SELECT CASE (clambert)
202  CASE ('L1 ')
203  ilambert=1
204  CASE ('L2 ')
205  ilambert=2
206  CASE ('L3 ')
207  ilambert=3
208  CASE ('L4 ')
209  ilambert=4
210  CASE ('L2E')
211  ilambert=5
212  CASE ('L93')
213  ilambert=6
214 END SELECT
215 !
216 !---------------------------------------------------------------------------
217 !
218 !* 7. maximum domain lengths
219 ! ----------------------
220 !
221 ALLOCATE(zxall(kl*3))
222 ALLOCATE(zyall(kl*3))
223  CALL get_xyall_ign(zx,zy,zdx,zdy,zxall,zyall,idimx,idimy)
224 !
225 !---------------------------------------------------------------------------
226 !
227 !* 8. All this information stored into pointer PGRID_PAR
228 ! --------------------------------------------------
229 !
230  CALL put_gridtype_ign(zgrid_par,ilambert,zx,zy,zdx,zdy, &
231  idimx,idimy,zxall(1:idimx),zyall(1:idimy))
232 !
233 !---------------------------------------------------------------------------
234 DEALLOCATE(zx)
235 DEALLOCATE(zy)
236 DEALLOCATE(zdx)
237 DEALLOCATE(zdy)
238 DEALLOCATE(zxall)
239 DEALLOCATE(zyall)
240 !---------------------------------------------------------------------------
241 !
242 !* 1st call : initializes dimension
243 !
244 IF (kgrid_par==0) THEN
245  kgrid_par = SIZE(zgrid_par)
246 !
247 ELSE
248 !
249 !* 2nd call : initializes grid array
250 !
251  pgrid_par(:) = 0.
252  pgrid_par(:) = zgrid_par
253 END IF
254 !
255 DEALLOCATE(zgrid_par)
256 IF (lhook) CALL dr_hook('READ_NAM_GRID_IGN',1,zhook_handle)
257 !
258 !---------------------------------------------------------------------------
259 !
260 END SUBROUTINE read_nam_grid_ign
subroutine get_xyall_ign(PX, PY, PDX, PDY, PXALL, PYALL, KDIMX, KDIMY)
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine put_gridtype_ign(PGRID_PAR, KLAMBERT, PX, PY, PDX, PDY, KDIMX, KDIMY, PXALL, PYALL)
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
subroutine read_nam_grid_ign(HPROGRAM, KGRID_PAR, KL, PGRID_PAR)