SURFEX v8.1
General documentation of Surfex
grid_modif_cartesian.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_cartesian(U,KLUOUT,KLUNAM,KGRID_PAR,KL,PGRID_PAR, &
7  KGRID_PAR2,KL2,OMODIF,PGRID_PAR2 )
8 ! ################################################################
9 !
10 !!**** *GRID_MODIF_CARTESIAN* - 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 #ifdef SFX_MNH
46 USE modd_spawn, ONLY : ndxratio,ndyratio,nxsize,nysize,nxor,nyor
47 #endif
48 
49 USE mode_pos_surf
51 !
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 INTEGER :: IIMAX1 ! number of points in I direction
82 INTEGER :: IJMAX1 ! number of points in J direction
83 REAL, DIMENSION(:), ALLOCATABLE :: ZX1 ! X conformal coordinate of grid mesh
84 REAL, DIMENSION(:), ALLOCATABLE :: ZY1 ! Y conformal coordinate of grid mesh
85 REAL, DIMENSION(:), ALLOCATABLE :: ZDX1 ! X grid mesh size
86 REAL, DIMENSION(:), ALLOCATABLE :: ZDY1 ! Y grid mesh size
87 !
88 !* new grid
89 INTEGER :: IIMAX2 ! number of points in I direction
90 INTEGER :: IJMAX2 ! number of points in J direction
91 REAL, DIMENSION(:), ALLOCATABLE :: ZX2 ! X conformal coordinate of grid mesh
92 REAL, DIMENSION(:), ALLOCATABLE :: ZY2 ! Y conformal coordinate of grid mesh
93 REAL, DIMENSION(:), ALLOCATABLE :: ZDX2 ! X grid mesh size
94 REAL, DIMENSION(:), ALLOCATABLE :: ZDY2 ! Y grid mesh size
95 !
96 !* other variables
97 LOGICAL :: GFOUND
98 REAL, DIMENSION(:), POINTER :: ZGRID_PAR
99 !
100 !
101 !* 0.3 Declarations of namelist
102 ! ------------------------
103 !
104 INTEGER :: IXOR = 1 ! position of modified bottom left point
105 INTEGER :: IYOR = 1 ! according to initial grid
106 INTEGER :: IXSIZE = -999 ! number of grid meshes in initial grid to be
107 INTEGER :: IYSIZE = -999 ! covered by the modified grid
108 INTEGER :: IDXRATIO = 1 ! resolution ratio between modified grid
109 INTEGER :: IDYRATIO = 1 ! and initial grid
110 REAL(KIND=JPRB) :: ZHOOK_HANDLE
111 !
112 !
113 NAMELIST/nam_inifile_cartesian/ixor,iyor,ixsize,iysize,idxratio,idyratio
114 !
115 !------------------------------------------------------------------------------
116 !
117 !* 1. Reading of projection parameters
118 ! --------------------------------
119 !
120 IF (lhook) CALL dr_hook('GRID_MODIF_CARTESIAN',0,zhook_handle)
121  CALL posnam(klunam,'NAM_INIFILE_CARTESIAN',gfound,kluout)
122 IF (gfound) READ(unit=klunam,nml=nam_inifile_cartesian)
123 !
124 #ifdef SFX_MNH
125 ! store the parameter in MODD_SPAWN
126 nxor = ixor
127 nyor = iyor
128 nxsize = ixsize
129 nysize = iysize
130 ndxratio = idxratio
131 ndyratio = idyratio
132 #endif
133 !
134 !---------------------------------------------------------------------------
135 !
136 !* 2. All this information stored into pointer PGRID_PAR
137 ! --------------------------------------------------
138 !
139 ALLOCATE(zx1(kl))
140 ALLOCATE(zy1(kl))
141 ALLOCATE(zdx1(kl))
142 ALLOCATE(zdy1(kl))
143 !
144  CALL get_gridtype_cartesian(pgrid_par,zlat0,zlon0, &
145  iimax1,ijmax1, &
146  zx1,zy1,zdx1,zdy1 )
147 !
148 !---------------------------------------------------------------------------
149 !
150 !* 3. Default : no modification
151 ! -------------------------
152 !
153 IF (ixsize==-999) ixsize=iimax1
154 IF (iysize==-999) iysize=ijmax1
155 !
156 !---------------------------------------------------------------------------
157 !
158 !* 4. Modification of the grid
159 ! ------------------------
160 !
161 !* number of points
162 !
163 iimax2=ixsize*idxratio
164 ijmax2=iysize*idyratio
165 !
166 kl2 = iimax2 * ijmax2
167 !
168  CALL regular_grid_spawn(u,kluout, &
169  kl, iimax1,ijmax1,zx1,zy1,zdx1,zdy1, &
170  ixor, iyor, idxratio, idyratio, &
171  ixsize, iysize, &
172  kl2, iimax2,ijmax2,zx2,zy2,zdx2,zdy2 )
173 DEALLOCATE(zx1)
174 DEALLOCATE(zy1)
175 DEALLOCATE(zdx1)
176 DEALLOCATE(zdy1)
177 !---------------------------------------------------------------------------
178 !
179 !* 5. All this information stored into pointer PGRID_PAR
180 ! --------------------------------------------------
181 !
182  CALL put_gridtype_cartesian(zgrid_par,zlat0,zlon0, &
183  iimax2,ijmax2, &
184  zx2,zy2,zdx2,zdy2 )
185 !
186 !---------------------------------------------------------------------------
187 DEALLOCATE(zx2)
188 DEALLOCATE(zy2)
189 DEALLOCATE(zdx2)
190 DEALLOCATE(zdy2)
191 !---------------------------------------------------------------------------
192 !
193 !* 1st call : initializes dimension
194 !
195 IF (kgrid_par2==0) THEN
196  kgrid_par2 = SIZE(zgrid_par)
197 !
198 ELSE
199 !
200 !* 2nd call : initializes grid array
201 !
202  pgrid_par2(:) = 0.
203  pgrid_par2(:) = zgrid_par
204 END IF
205 !
206 DEALLOCATE(zgrid_par)
207 IF (lhook) CALL dr_hook('GRID_MODIF_CARTESIAN',1,zhook_handle)
208 !
209 !---------------------------------------------------------------------------
210 !
211 END SUBROUTINE grid_modif_cartesian
subroutine regular_grid_spawn(U, KLUOUT,
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine put_gridtype_cartesian(PGRID_PAR, PLAT0, PLON0, KIMAX, KJMAX, PX, PY, PDX, PDY
integer, parameter jprb
Definition: parkind1.F90:32
integer, parameter nundef
subroutine grid_modif_cartesian(U, KLUOUT, KLUNAM, KGRID_PAR, KL, PGRID
logical lhook
Definition: yomhook.F90:15
subroutine get_gridtype_cartesian(PGRID_PAR, PLAT0, PLON0,