SURFEX v8.1
General documentation of Surfex
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(GCP,PGRID_FULL_PAR,KDIM_FULL,HPROGRAM,KGRID_PAR,KL,PGRID_PAR,HDIR)
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 !
42 !
44 !
45 USE mode_pos_surf
46 !
47 USE modi_open_namelist
48 USE modi_close_namelist
49 USE modi_get_luout
51 !
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 IMPLICIT NONE
58 !
59 !* 0.1 Declarations of arguments
60 ! -------------------------
61 !
62 TYPE(grid_conf_proj_t),INTENT(INOUT) :: GCP
63 !
64 REAL, DIMENSION(:), POINTER :: PGRID_FULL_PAR
65 INTEGER, INTENT(IN) :: KDIM_FULL
66 !
67  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! calling program
68 INTEGER, INTENT(INOUT) :: KGRID_PAR ! size of PGRID_PAR
69 INTEGER, INTENT(OUT) :: KL ! number of points
70 REAL, DIMENSION(KGRID_PAR), INTENT(OUT) :: PGRID_PAR ! parameters defining this grid
71  CHARACTER(LEN=1), INTENT(IN) :: HDIR
72 !
73 !* 0.2 Declarations of local variables
74 ! -------------------------------
75 !
76 INTEGER :: ILUOUT ! output listing logical unit
77 INTEGER :: ILUNAM ! namelist file logical unit
78 INTEGER :: JI, JJ ! loop counters
79 INTEGER :: JL ! loop counter
80 
81 REAL, DIMENSION(:), ALLOCATABLE :: ZX, ZX0 ! X conformal coordinate of grid mesh
82 REAL, DIMENSION(:), ALLOCATABLE :: ZY, ZY0 ! Y conformal coordinate of grid mesh
83 REAL, DIMENSION(:), ALLOCATABLE :: ZDX, ZDX0 ! X grid mesh size
84 REAL, DIMENSION(:), ALLOCATABLE :: ZDY, ZDY0 ! Y grid mesh size
85 REAL, DIMENSION(1) :: ZXOR ! X conformal coordinate of origine point
86 REAL, DIMENSION(1) :: ZYOR ! Y conformal coordinate of origin point
87 REAL, DIMENSION(1) :: ZLATOR ! latitude of origine point
88 REAL, DIMENSION(1) :: ZLONOR ! longitude of origin point
89 !
90 !* 0.3 Declarations of namelist
91 ! ------------------------
92 !
93 REAL :: XLAT0 ! reference latitude
94 REAL :: XLON0 ! reference longitude
95 REAL :: XRPK ! projection parameter
96 ! ! K=1 : stereographic north pole
97 ! ! 0<K<1 : Lambert, north hemisphere
98 ! ! K=0 : Mercator
99 ! !-1<K<0 : Lambert, south hemisphere
100 ! ! K=-1: stereographic south pole
101 REAL :: XBETA ! angle between grid and reference longitude
102 REAL :: XLATCEN ! latitude of center point
103 REAL :: XLONCEN ! longitude of center point
104 INTEGER :: NIMAX ! number of points in I direction
105 INTEGER :: NJMAX ! number of points in J direction
106 REAL :: XDX ! increment in X direction (in meters)
107 REAL :: XDY ! increment in Y direction (in meters)
108 !
109 REAL, DIMENSION(:), POINTER :: ZGRID_PAR
110 !
111 LOGICAL :: GFOUND
112 REAL(KIND=JPRB) :: ZHOOK_HANDLE
113 !
114 NAMELIST/nam_conf_proj/xlat0, xlon0, xrpk, xbeta
115 NAMELIST/nam_conf_proj_grid/nimax,njmax,xlatcen,xloncen,xdx,xdy
116 !
117 !------------------------------------------------------------------------------
118 !
119 !* 1. opening of namelist
120 !
121 IF (lhook) CALL dr_hook('READ_NAM_GRID_CONF_PROJ',0,zhook_handle)
122  CALL get_luout(hprogram,iluout)
123 !
124 IF (hdir/='H') THEN
125  !
126  CALL open_namelist(hprogram,ilunam)
127  !
128  !---------------------------------------------------------------------------
129  !
130  !* 2. Reading of projection parameters
131  ! --------------------------------
132  !
133  CALL posnam(ilunam,'NAM_CONF_PROJ',gfound,iluout)
134  IF (gfound) READ(unit=ilunam,nml=nam_conf_proj)
135  !
136  !---------------------------------------------------------------------------
137  !
138  !* 2. Reading parameters of the grid
139  ! ------------------------------
140  !
141  CALL posnam(ilunam,'NAM_CONF_PROJ_GRID',gfound,iluout)
142  IF (gfound) READ(unit=ilunam,nml=nam_conf_proj_grid)
143  !
144  !---------------------------------------------------------------------------
145  CALL close_namelist(hprogram,ilunam)
146  !---------------------------------------------------------------------------
147  !
148  !* 3. Number of points
149  ! ----------------
150  !
151  kl = nimax * njmax
152  !
153  !---------------------------------------------------------------------------
154  !
155  !* 3. Array of X and Y coordinates
156  ! ----------------------------
157  !
158  !
159  ALLOCATE(zx(kl))
160  ALLOCATE(zy(kl))
161  DO jj=1,njmax
162  DO ji=1,nimax
163  jl = ji + (jj-1) * nimax
164  zx(jl) = float(ji) * xdx
165  zy(jl) = float(jj) * xdy
166  END DO
167  END DO
168  !
169  !---------------------------------------------------------------------------
170  !
171  !* 4. Array of X and Y increments
172  ! ---------------------------
173  !
174  ALLOCATE(zdx(kl))
175  ALLOCATE(zdy(kl))
176  zdx(:) = xdx
177  zdy(:) = xdy
178  !
179  !---------------------------------------------------------------------------
180  !
181  !* 5. Latitude and longitude of point of coordinates 0,0
182  ! --------------------------------------------------
183  !
184  ! Coordinates of origin point are here defined from center point, that
185  ! is then used as substitute reference point.
186  ! In all further computations, origin point will be of course be x=0, y=0
187  !
188  zxor = - float(nimax+1)/2.*xdx
189  zyor = - float(njmax+1)/2.*xdy
190  !
191  CALL latlon_conf_proj(xlat0,xlon0,xrpk,xbeta,xlatcen,xloncen, &
192  zxor,zyor,zlator,zlonor )
193  !
194  gcp%XLATC=xlatcen
195  gcp%XLONC=xloncen
196  !
197 ELSE
198  !
199  !
200  ALLOCATE(zx0(kdim_full),zy0(kdim_full),zdx0(kdim_full),zdy0(kdim_full))
201  CALL get_gridtype_conf_proj(pgrid_full_par,plat0=xlat0,plon0=xlon0,&
202  prpk=xrpk,pbeta=xbeta,plator=zlator(1),&
203  plonor=zlonor(1),kimax=nimax,kjmax=njmax,&
204  px=zx0,py=zy0,pdx=zdx0,pdy=zdy0)
205  !
206  kl = nsize_task(nrank)
207  ALLOCATE(zx(kl),zy(kl),zdx(kl),zdy(kl))
208  !
209  CALL read_and_send_mpi(zx0,zx)
210  CALL read_and_send_mpi(zy0,zy)
211  CALL read_and_send_mpi(zdx0,zdx)
212  CALL read_and_send_mpi(zdy0,zdy)
213  !
214  IF (nrank==npio) DEALLOCATE(zx0,zy0,zdx0,zdy0)
215  !
216 ENDIF
217 !---------------------------------------------------------------------------
218 !
219 !* 8. All this information stored into pointer PGRID_PAR
220 ! --------------------------------------------------
221 !
222  CALL put_gridtype_conf_proj(zgrid_par,xlat0,xlon0,xrpk,xbeta, &
223  zlator(1),zlonor(1),nimax,njmax, &
224  zx,zy,zdx,zdy )
225 !
226 !---------------------------------------------------------------------------
227 DEALLOCATE(zx)
228 DEALLOCATE(zy)
229 DEALLOCATE(zdx)
230 DEALLOCATE(zdy)
231 !---------------------------------------------------------------------------
232 !
233 !* 1st call : initializes dimension
234 !
235 IF (kgrid_par==0) THEN
236  kgrid_par = SIZE(zgrid_par)
237 !
238 ELSE
239 !
240 !* 2nd call : initializes grid array
241 !
242  pgrid_par(:) = 0.
243  pgrid_par(:) = zgrid_par
244 END IF
245 !
246 DEALLOCATE(zgrid_par)
247 IF (lhook) CALL dr_hook('READ_NAM_GRID_CONF_PROJ',1,zhook_handle)
248 !
249 !---------------------------------------------------------------------------
250 !
251 END SUBROUTINE read_nam_grid_conf_proj
subroutine latlon_conf_proj(PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR,
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
integer, parameter jprb
Definition: parkind1.F90:32
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
integer, dimension(:), allocatable nsize_task
subroutine get_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA
logical lhook
Definition: yomhook.F90:15
subroutine read_nam_grid_conf_proj(GCP, PGRID_FULL_PAR, KDIM_FULL, HP
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
subroutine put_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA