SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
zoom_pgd_orography.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 zoom_pgd_orography (DTCO, &
7  ug, u, uss, &
8  hprogram,psea,pwater,hinifile,hinifiletype)
9 ! ###########################################################
10 
11 !!
12 !! PURPOSE
13 !! -------
14 !! This program prepares the physiographic data fields.
15 !!
16 !! METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !! AUTHOR
31 !! ------
32 !!
33 !! V. Masson Meteo-France
34 !!
35 !! MODIFICATION
36 !! ------------
37 !!
38 !! Original 13/10/03
39 !----------------------------------------------------------------------------
40 !
41 !* 0. DECLARATION
42 ! -----------
43 !
44 !
45 !
46 !
47 !
49 !
51 USE modd_surf_atm_n, ONLY : surf_atm_t
53 !
54 USE modd_prep, ONLY : cingrid_type, cinterp_type, linterp
55 USE modd_surf_par, ONLY : xundef
56 !
57 USE modi_open_aux_io_surf
59 USE modi_close_aux_io_surf
60 USE modi_prep_grid_extern
61 USE modi_hor_interpol
62 USE modi_prep_output_grid
63 !
64 !
65 USE yomhook ,ONLY : lhook, dr_hook
66 USE parkind1 ,ONLY : jprb
67 !
68 USE modi_clean_prep_output_grid
69 !
70 USE modi_get_luout
71 IMPLICIT NONE
72 !
73 !* 0.1 Declaration of dummy arguments
74 ! ------------------------------
75 !
76 !
77 !
78 TYPE(data_cover_t), INTENT(INOUT) :: dtco
79 !
80 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
81 TYPE(surf_atm_t), INTENT(INOUT) :: u
82 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
83 !
84  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
85 REAL, DIMENSION(:), INTENT(IN) :: psea ! sea fraction
86 REAL, DIMENSION(:), INTENT(IN) :: pwater ! inland water fraction
87  CHARACTER(LEN=28), INTENT(IN) :: hinifile ! input atmospheric file name
88  CHARACTER(LEN=6), INTENT(IN) :: hinifiletype! input atmospheric file type
89 !
90 !
91 !* 0.2 Declaration of local variables
92 ! ------------------------------
93 !
94 INTEGER :: iresp
95 INTEGER :: iluout
96 INTEGER :: ini ! total 1D dimension (input field)
97 INTEGER :: il ! total 1D dimension (output field)
98 REAL, DIMENSION(:), POINTER :: zzs
99 REAL, DIMENSION(:), POINTER :: zavg_zs
100 REAL, DIMENSION(:), POINTER :: zsil_zs
101 REAL, DIMENSION(:), POINTER :: zsso_stdev
102 REAL, DIMENSION(:), POINTER :: zmin_zs
103 REAL, DIMENSION(:), POINTER :: zmax_zs
104 REAL, DIMENSION(:), POINTER :: zsso_anis
105 REAL, DIMENSION(:), POINTER :: zsso_dir
106 REAL, DIMENSION(:), POINTER :: zsso_slope
107 REAL, DIMENSION(:), POINTER :: zaosip
108 REAL, DIMENSION(:), POINTER :: zaosim
109 REAL, DIMENSION(:), POINTER :: zaosjp
110 REAL, DIMENSION(:), POINTER :: zaosjm
111 REAL, DIMENSION(:), POINTER :: zho2ip
112 REAL, DIMENSION(:), POINTER :: zho2im
113 REAL, DIMENSION(:), POINTER :: zho2jp
114 REAL, DIMENSION(:), POINTER :: zho2jm
115  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
116 REAL(KIND=JPRB) :: zhook_handle
117 !------------------------------------------------------------------------------
118 IF (lhook) CALL dr_hook('ZOOM_PGD_OROGRAPHY',0,zhook_handle)
119  CALL get_luout(hprogram,iluout)
120 !
121 !* 1. Preparation of IO for reading in the file
122 ! -----------------------------------------
123 !
124 !* Note that all points are read, even those without physical meaning.
125 ! These points will not be used during the horizontal interpolation step.
126 ! Their value must be defined as XUNDEF.
127 !
128  CALL open_aux_io_surf(&
129  hinifile,hinifiletype,'FULL ')
130 !
131 !------------------------------------------------------------------------------
132 !
133 !* 2. Reading of grid
134 ! ---------------
135 !
136  CALL prep_grid_extern(&
137  hinifiletype,iluout,cingrid_type,cinterp_type,ini)
138 !
139  CALL prep_output_grid(ug, u, &
140  iluout,ug%CGRID,ug%XGRID_PAR,ug%XLAT,ug%XLON)
141 !
142 !------------------------------------------------------------------------------
143 !
144 !* 3. Reading of orographic parameters
145 ! --------------------------------
146 !
147 ALLOCATE(zzs(ini))
148 !
149 ALLOCATE(zavg_zs(ini))
150 ALLOCATE(zsil_zs(ini))
151 ALLOCATE(zsso_stdev(ini))
152 ALLOCATE(zmin_zs(ini))
153 ALLOCATE(zmax_zs(ini))
154 !
155 ALLOCATE(zsso_anis(ini))
156 ALLOCATE(zsso_dir(ini))
157 ALLOCATE(zsso_slope(ini))
158 !
159 ALLOCATE(zaosip(ini))
160 ALLOCATE(zaosim(ini))
161 ALLOCATE(zaosjp(ini))
162 ALLOCATE(zaosjm(ini))
163 ALLOCATE(zho2ip(ini))
164 ALLOCATE(zho2im(ini))
165 ALLOCATE(zho2jp(ini))
166 ALLOCATE(zho2jm(ini))
167 !
168 yrecfm='ZS'
169  CALL read_surf(&
170  hprogram,yrecfm,zzs,iresp,hdir='A')
171 !
172 yrecfm='AVG_ZS'
173  CALL read_surf(&
174  hprogram,yrecfm,zavg_zs,iresp,hdir='A')
175 yrecfm='SIL_ZS'
176  CALL read_surf(&
177  hprogram,yrecfm,zsil_zs,iresp,hdir='A')
178 yrecfm='SSO_STDEV'
179  CALL read_surf(&
180  hprogram,yrecfm,zsso_stdev,iresp,hdir='A')
181 yrecfm='MIN_ZS'
182  CALL read_surf(&
183  hprogram,yrecfm,zmin_zs,iresp,hdir='A')
184 yrecfm='MAX_ZS'
185  CALL read_surf(&
186  hprogram,yrecfm,zmax_zs,iresp,hdir='A')
187 !
188 yrecfm='SSO_ANIS'
189  CALL read_surf(&
190  hprogram,yrecfm,zsso_anis,iresp,hdir='A')
191 yrecfm='SSO_DIR'
192  CALL read_surf(&
193  hprogram,yrecfm,zsso_dir,iresp,hdir='A')
194 yrecfm='SSO_SLOPE'
195  CALL read_surf(&
196  hprogram,yrecfm,zsso_slope,iresp,hdir='A')
197 !
198 yrecfm='AOSIP'
199  CALL read_surf(&
200  hprogram,yrecfm,zaosip,iresp,hdir='A')
201 yrecfm='AOSIM'
202  CALL read_surf(&
203  hprogram,yrecfm,zaosim,iresp,hdir='A')
204 yrecfm='AOSJP'
205  CALL read_surf(&
206  hprogram,yrecfm,zaosjp,iresp,hdir='A')
207 yrecfm='AOSJM'
208  CALL read_surf(&
209  hprogram,yrecfm,zaosjm,iresp,hdir='A')
210 yrecfm='HO2IP'
211  CALL read_surf(&
212  hprogram,yrecfm,zho2ip,iresp,hdir='A')
213 yrecfm='HO2IM'
214  CALL read_surf(&
215  hprogram,yrecfm,zho2im,iresp,hdir='A')
216 yrecfm='HO2JP'
217  CALL read_surf(&
218  hprogram,yrecfm,zho2jp,iresp,hdir='A')
219 yrecfm='HO2JM'
220  CALL read_surf(&
221  hprogram,yrecfm,zho2jm,iresp,hdir='A')
222 !
223  CALL close_aux_io_surf(hinifile,hinifiletype)
224 !------------------------------------------------------------------------------
225 !
226 !* 4. Interpolations
227 ! --------------
228 !
229 il = SIZE(ug%XLAT)
230 !
231 ALLOCATE(u%XZS (il))
232 !
233 ALLOCATE(uss%XAVG_ZS (il))
234 ALLOCATE(uss%XSIL_ZS (il))
235 ALLOCATE(uss%XSSO_STDEV (il))
236 ALLOCATE(uss%XMIN_ZS (il))
237 ALLOCATE(uss%XMAX_ZS (il))
238 !
239 ALLOCATE(uss%XSSO_ANIS (il))
240 ALLOCATE(uss%XSSO_DIR (il))
241 ALLOCATE(uss%XSSO_SLOPE (il))
242 !
243 ALLOCATE(uss%XAOSIP (il))
244 ALLOCATE(uss%XAOSIM (il))
245 ALLOCATE(uss%XAOSJP (il))
246 ALLOCATE(uss%XAOSJM (il))
247 ALLOCATE(uss%XHO2IP (il))
248 ALLOCATE(uss%XHO2IM (il))
249 ALLOCATE(uss%XHO2JP (il))
250 ALLOCATE(uss%XHO2JM (il))
251 !
252  CALL zoom(iluout,zzs,u%XZS)
253  CALL zoom(iluout,zavg_zs,uss%XAVG_ZS)
254  CALL zoom(iluout,zsil_zs,uss%XSIL_ZS)
255  CALL zoom(iluout,zmin_zs,uss%XMIN_ZS)
256  CALL zoom(iluout,zmax_zs,uss%XMAX_ZS)
257 !
258 linterp(:)=(psea(:)<1.)
259  CALL zoom(iluout,zsso_stdev,uss%XSSO_STDEV)
260  CALL zoom(iluout,zsso_anis,uss%XSSO_ANIS)
261  CALL zoom(iluout,zsso_dir,uss%XSSO_DIR)
262  CALL zoom(iluout,zsso_slope,uss%XSSO_SLOPE)
263  CALL zoom(iluout,zaosip,uss%XAOSIP)
264  CALL zoom(iluout,zaosim,uss%XAOSIM)
265  CALL zoom(iluout,zaosjp,uss%XAOSJP)
266  CALL zoom(iluout,zaosjm,uss%XAOSJM)
267  CALL zoom(iluout,zho2ip,uss%XHO2IP)
268  CALL zoom(iluout,zho2im,uss%XHO2IM)
269  CALL zoom(iluout,zho2jp,uss%XHO2JP)
270  CALL zoom(iluout,zho2jm,uss%XHO2JM)
271 !
272 !* coherence with land sea mask
273 !
274 WHERE(psea==1.) u%XZS=0.
275 WHERE(psea(:)==1.) uss%XSSO_STDEV(:) = xundef
276 WHERE(pwater(:)==1.) uss%XSSO_STDEV(:) = 0.
277 WHERE(psea(:)>0.) uss%XMIN_ZS(:) = 0.
278 WHERE(psea(:)==1.) uss%XMAX_ZS(:) = 0.
279 !
280 WHERE (psea(:)==1.)
281  uss%XSSO_ANIS (:) = xundef
282  uss%XSSO_DIR (:) = xundef
283  uss%XSSO_SLOPE(:) = xundef
284 END WHERE
285 !
286 WHERE (pwater(:)==1.)
287  uss%XSSO_ANIS (:) = 1.
288  uss%XSSO_DIR (:) = 0.
289  uss%XSSO_SLOPE(:) = 0.
290 END WHERE
291 !
292 WHERE (psea(:)==1.)
293  uss%XHO2IP(:) = xundef
294  uss%XHO2IM(:) = xundef
295  uss%XHO2JP(:) = xundef
296  uss%XHO2JM(:) = xundef
297  uss%XAOSIP(:) = xundef
298  uss%XAOSIM(:) = xundef
299  uss%XAOSJP(:) = xundef
300  uss%XAOSJM(:) = xundef
301 END WHERE
302 !
303 WHERE (pwater(:)==1.)
304  uss%XHO2IP(:) = 0.
305  uss%XHO2IM(:) = 0.
306  uss%XHO2JP(:) = 0.
307  uss%XHO2JM(:) = 0.
308  uss%XAOSIP(:) = 0.
309  uss%XAOSIM(:) = 0.
310  uss%XAOSJP(:) = 0.
311  uss%XAOSJM(:) = 0.
312 END WHERE
313 !_______________________________________________________________________________
314 DEALLOCATE(zzs )
315 !
316 DEALLOCATE(zavg_zs )
317 DEALLOCATE(zsil_zs )
318 DEALLOCATE(zsso_stdev )
319 DEALLOCATE(zmin_zs )
320 DEALLOCATE(zmax_zs )
321 !
322 DEALLOCATE(zsso_anis )
323 DEALLOCATE(zsso_dir )
324 DEALLOCATE(zsso_slope )
325 !
326 DEALLOCATE(zaosip )
327 DEALLOCATE(zaosim )
328 DEALLOCATE(zaosjp )
329 DEALLOCATE(zaosjm )
330 DEALLOCATE(zho2ip )
331 DEALLOCATE(zho2im )
332 DEALLOCATE(zho2jp )
333 DEALLOCATE(zho2jm )
334 !_______________________________________________________________________________
336 !_______________________________________________________________________________
337 IF (lhook) CALL dr_hook('ZOOM_PGD_OROGRAPHY',1,zhook_handle)
338  CONTAINS
339 !
340 SUBROUTINE zoom(KLUOUT,PFIELDIN,PFIELDOUT)
341 INTEGER, INTENT(IN) :: kluout
342 REAL, DIMENSION(:), POINTER :: pfieldin
343 REAL, DIMENSION(:), INTENT(OUT) :: pfieldout
344 REAL, DIMENSION(:,:), POINTER :: zfieldin
345 REAL, DIMENSION(:,:), POINTER :: zfieldout
346 REAL(KIND=JPRB) :: zhook_handle
347 IF (lhook) CALL dr_hook('ZOOM',0,zhook_handle)
348 ALLOCATE(zfieldin(SIZE(pfieldin, 1),1))
349 ALLOCATE(zfieldout(SIZE(pfieldout,1),1))
350 zfieldin(:,1) = pfieldin(:)
351  CALL hor_interpol(dtco, u, &
352  kluout,zfieldin,zfieldout)
353 pfieldout(:) = zfieldout(:,1)
354 DEALLOCATE(zfieldin )
355 DEALLOCATE(zfieldout)
356 IF (lhook) CALL dr_hook('ZOOM',1,zhook_handle)
357 
358 END SUBROUTINE zoom
359 !
360 END SUBROUTINE zoom_pgd_orography
subroutine zoom_pgd_orography(DTCO, UG, U, USS, HPROGRAM, PSEA, PWATER, HINIFILE, HINIFILETYPE)
subroutine clean_prep_output_grid
subroutine close_aux_io_surf(HFILE, HFILETYPE)
subroutine hor_interpol(DTCO, U, KLUOUT, PFIELDIN, PFIELDOUT)
Definition: hor_interpol.F90:6
subroutine open_aux_io_surf(HFILE, HFILETYPE, HMASK)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine zoom(KLUOUT, PFIELDIN, PFIELDOUT)
subroutine prep_grid_extern(HFILETYPE, KLUOUT, HGRIDTYPE, HINTERP_TYPE, KNI)
subroutine prep_output_grid(UG, U, KLUOUT, HGRID, PGRID_PAR, PLAT, PLON)