SURFEX v8.1
General documentation of Surfex
grid_modif_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 grid_modif_conf_proj(U,KLUOUT,KLUNAM,KGRID_PAR,KL,PGRID_PAR, &
7  KGRID_PAR2,KL2,OMODIF,PGRID_PAR2 )
8 ! ################################################################
9 !
10 !!**** *GRID_MODIF_CONF_PROJ* - routine to read in namelist the horizontal grid
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !! V. Masson *Meteo France*
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 01/2004
36 !! M.Moge 06/2015 Initialization of MODD_SPAWN variables
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 USE modd_surf_atm_n, ONLY : surf_atm_t
43 !
44 USE modd_surf_par, ONLY : nundef
45 !
46 #ifdef SFX_MNH
47 USE modd_spawn, ONLY : ndxratio,ndyratio,nxsize,nysize,nxor,nyor
48 #endif
49 !
50 USE mode_pos_surf
52 !
53 USE yomhook ,ONLY : lhook, dr_hook
54 USE parkind1 ,ONLY : jprb
55 !
56 USE modi_regular_grid_spawn
57 !
58 IMPLICIT NONE
59 !
60 !* 0.1 Declarations of arguments
61 ! -------------------------
62 !
63 TYPE(surf_atm_t), INTENT(INOUT) :: U
64 !
65 INTEGER, INTENT(IN) :: KLUOUT ! output listing logical unit
66 INTEGER, INTENT(IN) :: KLUNAM ! namelist file logical unit
67 INTEGER, INTENT(IN) :: KL ! number of points
68 INTEGER, INTENT(IN) :: KGRID_PAR ! size of PGRID_PAR
69 REAL, DIMENSION(KGRID_PAR), INTENT(IN) :: PGRID_PAR ! parameters defining the grid
70 INTEGER, INTENT(INOUT) :: KL2 ! number of points in modified grid
71 INTEGER, INTENT(INOUT) :: KGRID_PAR2 ! size of PGRID_PAR2
72 LOGICAL, INTENT(IN) :: OMODIF ! flag to modify the grid
73 REAL, DIMENSION(KGRID_PAR2), INTENT(OUT) :: PGRID_PAR2 ! parameters defining the modified grid
74 !
75 !* 0.2 Declarations of local variables
76 ! -------------------------------
77 !
78 !* initial grid
79 REAL :: ZLAT0 ! reference latitude
80 REAL :: ZLON0 ! reference longitude
81 REAL :: ZRPK ! projection parameter
82 ! ! K=1 : stereographic north pole
83 ! ! 0<K<1 : Lambert, north hemisphere
84 ! ! K=0 : Mercator
85 ! !-1<K<0 : Lambert, south hemisphere
86 ! ! K=-1: stereographic south pole
87 REAL :: ZBETA ! angle between grid and reference longitude
88 REAL :: ZLATOR ! latitude of point of coordinates X=0, Y=0
89 REAL :: ZLONOR ! longitude of point of coordinates X=0, Y=0
90 INTEGER :: IIMAX1 ! number of points in I direction
91 INTEGER :: IJMAX1 ! number of points in J direction
92 REAL, DIMENSION(:), ALLOCATABLE :: ZX1 ! X conformal coordinate of grid mesh
93 REAL, DIMENSION(:), ALLOCATABLE :: ZY1 ! Y conformal coordinate of grid mesh
94 REAL, DIMENSION(:), ALLOCATABLE :: ZDX1 ! X grid mesh size
95 REAL, DIMENSION(:), ALLOCATABLE :: ZDY1 ! Y grid mesh size
96 !
97 !* new grid
98 INTEGER :: IIMAX2 ! number of points in I direction
99 INTEGER :: IJMAX2 ! number of points in J direction
100 REAL, DIMENSION(:), ALLOCATABLE :: ZX2 ! X conformal coordinate of grid mesh
101 REAL, DIMENSION(:), ALLOCATABLE :: ZY2 ! Y conformal coordinate of grid mesh
102 REAL, DIMENSION(:), ALLOCATABLE :: ZDX2 ! X grid mesh size
103 REAL, DIMENSION(:), ALLOCATABLE :: ZDY2 ! Y grid mesh size
104 !
105 !* other variables
106 LOGICAL :: GFOUND
107 REAL, DIMENSION(:), POINTER :: ZGRID_PAR
108 !
109 !
110 !* 0.3 Declarations of namelist
111 ! ------------------------
112 !
113 INTEGER :: IXOR = 1 ! position of modified bottom left point
114 INTEGER :: IYOR = 1 ! according to initial grid
115 INTEGER :: IXSIZE = -999 ! number of grid meshes in initial grid to be
116 INTEGER :: IYSIZE = -999 ! covered by the modified grid
117 INTEGER :: IDXRATIO = 1 ! resolution ratio between modified grid
118 INTEGER :: IDYRATIO = 1 ! and initial grid
119 REAL(KIND=JPRB) :: ZHOOK_HANDLE
120 !
121 !
122 NAMELIST/nam_inifile_conf_proj/ixor,iyor,ixsize,iysize,idxratio,idyratio
123 !
124 !------------------------------------------------------------------------------
125 !
126 !* 1. Reading of projection parameters
127 ! --------------------------------
128 !
129 IF (lhook) CALL dr_hook('GRID_MODIF_CONF_PROJ',0,zhook_handle)
130  CALL posnam(klunam,'NAM_INIFILE_CONF_PROJ',gfound,kluout)
131 IF (gfound) READ(unit=klunam,nml=nam_inifile_conf_proj)
132 !
133 #ifdef SFX_MNH
134 ! store the parameter in MODD_SPAWN
135 nxor = ixor
136 nyor = iyor
137 nxsize = ixsize
138 nysize = iysize
139 ndxratio = idxratio
140 ndyratio = idyratio
141 #endif
142 !
143 !---------------------------------------------------------------------------
144 !
145 !* 2. All this information stored into pointer PGRID_PAR
146 ! --------------------------------------------------
147 !
148 ALLOCATE(zx1(kl))
149 ALLOCATE(zy1(kl))
150 ALLOCATE(zdx1(kl))
151 ALLOCATE(zdy1(kl))
152 !
153  CALL get_gridtype_conf_proj(pgrid_par,zlat0,zlon0,zrpk,zbeta, &
154  zlator,zlonor, &
155  iimax1,ijmax1, &
156  zx1,zy1,zdx1,zdy1 )
157 !
158 !---------------------------------------------------------------------------
159 !
160 !* 3. Default : no modification
161 ! -------------------------
162 !
163 IF (ixsize==-999) ixsize=iimax1
164 IF (iysize==-999) iysize=ijmax1
165 !
166 !---------------------------------------------------------------------------
167 !
168 !* 4. Modification of the grid
169 ! ------------------------
170 !
171 !* number of points
172 !
173 iimax2=ixsize*idxratio
174 ijmax2=iysize*idyratio
175 !
176 kl2 = iimax2 * ijmax2
177 !
178  CALL regular_grid_spawn(u,kluout, &
179  kl, iimax1,ijmax1,zx1,zy1,zdx1,zdy1, &
180  ixor, iyor, idxratio, idyratio, &
181  ixsize, iysize, &
182  kl2, iimax2,ijmax2,zx2,zy2,zdx2,zdy2 )
183 DEALLOCATE(zx1)
184 DEALLOCATE(zy1)
185 DEALLOCATE(zdx1)
186 DEALLOCATE(zdy1)
187 !
188 !---------------------------------------------------------------------------
189 !
190 !* 5. All this information stored into pointer PGRID_PAR
191 ! --------------------------------------------------
192 !
193  CALL put_gridtype_conf_proj(zgrid_par,zlat0,zlon0,zrpk,zbeta, &
194  zlator,zlonor, &
195  iimax2,ijmax2, &
196  zx2,zy2,zdx2,zdy2 )
197 !
198 !---------------------------------------------------------------------------
199 DEALLOCATE(zx2)
200 DEALLOCATE(zy2)
201 DEALLOCATE(zdx2)
202 DEALLOCATE(zdy2)
203 !---------------------------------------------------------------------------
204 !
205 !* 1st call : initializes dimension
206 !
207 IF (kgrid_par2==0) THEN
208  kgrid_par2 = SIZE(zgrid_par)
209 !
210 ELSE
211 !
212 !* 2nd call : initializes grid array
213 !
214  pgrid_par2(:) = 0.
215  pgrid_par2(:) = zgrid_par
216 END IF
217 !
218 DEALLOCATE(zgrid_par)
219 IF (lhook) CALL dr_hook('GRID_MODIF_CONF_PROJ',1,zhook_handle)
220 !
221 !---------------------------------------------------------------------------
222 !
223 END SUBROUTINE grid_modif_conf_proj
subroutine regular_grid_spawn(U, KLUOUT,
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
integer, parameter jprb
Definition: parkind1.F90:32
integer, parameter nundef
subroutine get_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA
logical lhook
Definition: yomhook.F90:15
subroutine grid_modif_conf_proj(U, KLUOUT, KLUNAM, KGRID_PAR, KL, PGRID
subroutine put_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA