SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_pgd_isban.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 writesurf_pgd_isba_n (DGU, &
7  dti, dtz, ig, i, u, &
8  hprogram)
9 ! ################################################
10 !
11 !!**** *WRITESURF_PGD_ISBA_n* - writes ISBA physiographic fields
12 !!
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !!
31 !! AUTHOR
32 !! ------
33 !! V. Masson *Meteo France*
34 !!
35 !! MODIFICATIONS
36 !! -------------
37 !! Original 01/2003
38 !! P. Le Moigne 12/2004 : add type of photosynthesis
39 !! B. Decharme 06/2009 : add topographic index statistics
40 !! A.L. Gibelin 04/2009 : dimension NBIOMASS for ISBA-A-gs
41 !! B. Decharme 07/2011 : delete argument HWRITE
42 !! B. Decharme 07/2012 : files of data for permafrost area and for SOC top and sub soil
43 !! 11/2013 : same for groundwater distribution
44 !! 11/2014 : Write XSOILGRID as a series of real
45 !! P. Samuelsson 10/2014 : MEB
46 !!
47 !-------------------------------------------------------------------------------
48 !
49 !* 0. DECLARATIONS
50 ! ------------
51 !
52 !
53 !
54 !
55 !
56 !
57 !
58 !
60 !
61 USE modd_data_isba_n, ONLY : data_isba_t
62 USE modd_data_tsz0_n, ONLY : data_tsz0_t
63 USE modd_isba_grid_n, ONLY : isba_grid_t
64 USE modd_isba_n, ONLY : isba_t
65 USE modd_surf_atm_n, ONLY : surf_atm_t
66 !
67 USE modd_data_cover_par, ONLY : jpcover
68 !
70 !
72 USE modi_write_grid
73 USE modi_writesurf_pgd_isba_par_n
74 USE modi_writesurf_pgd_tsz0_par_n
75 !
76 USE yomhook ,ONLY : lhook, dr_hook
77 USE parkind1 ,ONLY : jprb
78 !
79 IMPLICIT NONE
80 !
81 !* 0.1 Declarations of arguments
82 ! -------------------------
83 !
84 !
85 !
86 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
87 !
88 TYPE(data_isba_t), INTENT(INOUT) :: dti
89 TYPE(data_tsz0_t), INTENT(INOUT) :: dtz
90 TYPE(isba_grid_t), INTENT(INOUT) :: ig
91 TYPE(isba_t), INTENT(INOUT) :: i
92 TYPE(surf_atm_t), INTENT(INOUT) :: u
93 !
94  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
95 !
96 !* 0.2 Declarations of local variables
97 ! -------------------------------
98 !
99 INTEGER :: iresp ! IRESP : return-code if a problem appears
100  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
101  CHARACTER(LEN=100):: ycomment ! Comment string
102  CHARACTER(LEN=4 ) :: ylvl
103 !
104 INTEGER :: jj, jlayer
105 INTEGER :: isize_lmeb_patch ! Number of patches with MEB=true
106 !
107 REAL(KIND=JPRB) :: zhook_handle
108 !
109 !
110 !-------------------------------------------------------------------------------
111 !
112 !
113 !* soil scheme option
114 !
115 IF (lhook) CALL dr_hook('WRITESURF_PGD_ISBA_N',0,zhook_handle)
116 yrecfm='ISBA'
117 ycomment=yrecfm
118  CALL write_surf(dgu, u, &
119  hprogram,yrecfm,i%CISBA,iresp,hcomment=ycomment)
120 !
121 !* Pedo-transfert function
122 !
123 yrecfm='PEDOTF'
124 ycomment=yrecfm
125  CALL write_surf(dgu, u, &
126  hprogram,yrecfm,i%CPEDOTF,iresp,hcomment=ycomment)
127 !
128 !* type of photosynthesis
129 !
130 yrecfm='PHOTO'
131 ycomment=yrecfm
132  CALL write_surf(dgu, u, &
133  hprogram,yrecfm,i%CPHOTO,iresp,hcomment=ycomment)
134 !
135 !* new radiative transfert
136 !
137 yrecfm='TR_ML'
138 ycomment=yrecfm
139  CALL write_surf(dgu, u, &
140  hprogram,yrecfm,i%LTR_ML,iresp,hcomment=ycomment)
141 !
142 !* threshold to remove little fractions of patches
143 !
144 yrecfm='RM_PATCH'
145 ycomment=yrecfm
146  CALL write_surf(dgu, u, &
147  hprogram,yrecfm,i%XRM_PATCH,iresp,hcomment=ycomment)
148 
149 !* number of soil layers
150 !
151 yrecfm='GROUND_LAYER'
152 ycomment=yrecfm
153  CALL write_surf(dgu, u, &
154  hprogram,yrecfm,i%NGROUND_LAYER,iresp,hcomment=ycomment)
155 !
156 !* Reference grid for DIF
157 !
158 IF(i%CISBA=='DIF') THEN
159  DO jlayer=1,i%NGROUND_LAYER
160  WRITE(ylvl,'(I4)') jlayer
161  yrecfm='SOILGRID'//adjustl(ylvl(:len_trim(ylvl)))
162  ycomment='Depth of ISBA soilgrid layer '//adjustl(ylvl(:len_trim(ylvl)))
163  CALL write_surf(dgu, u, &
164  hprogram,yrecfm,i%XSOILGRID(jlayer),iresp,hcomment=ycomment)
165  END DO
166 ENDIF
167 !
168 !* number of biomass pools
169 !
170 yrecfm='NBIOMASS'
171 ycomment=yrecfm
172  CALL write_surf(dgu, u, &
173  hprogram,yrecfm,i%NNBIOMASS,iresp,hcomment=ycomment)
174 !
175 !* number of tiles
176 !
177 yrecfm='PATCH_NUMBER'
178 ycomment=yrecfm
179  CALL write_surf(dgu, u, &
180  hprogram,yrecfm,i%NPATCH,iresp,hcomment=ycomment)
181 !
182 !* flag indicating if fields are computed from ecoclimap or not
183 !
184 yrecfm='ECOCLIMAP'
185 ycomment=yrecfm
186  CALL write_surf(dgu, u, &
187  hprogram,yrecfm,i%LECOCLIMAP,iresp,hcomment=ycomment)
188 !
189 !* logical vector indicating for which patches MEB should be applied
190 !
191 yrecfm='MEB_PATCH'
192 ycomment='(LOGICAL LIST)'
193  CALL write_surf(dgu, u, &
194  hprogram,yrecfm,i%LMEB_PATCH(:),iresp,hcomment=ycomment,hdir='-')
195 !
196 isize_lmeb_patch = count(i%LMEB_PATCH(:))
197 !
198 IF (isize_lmeb_patch>0)THEN
199 !
200 !* flag indicating if forcing is from observed measurements or not
201 !
202  yrecfm='FORC_MEASURE'
203  ycomment=yrecfm
204  CALL write_surf(dgu, u, &
205  hprogram,yrecfm,i%LFORC_MEASURE,iresp,hcomment=ycomment)
206 !
207 !* flag indicating if litter layer is used or not
208 !
209  yrecfm='MEB_LITTER'
210  ycomment=yrecfm
211  CALL write_surf(dgu, u, &
212  hprogram,yrecfm,i%LMEB_LITTER,iresp,hcomment=ycomment)
213 !
214 !* flag indicating if ground resistance is used or not
215 !
216  yrecfm='MEB_GNDRES'
217  ycomment=yrecfm
218  CALL write_surf(dgu, u, &
219  hprogram,yrecfm,i%LMEB_GNDRES,iresp,hcomment=ycomment)
220 !
221 ENDIF
222 !
223 !* 2. Physiographic data fields:
224 ! -------------------------
225 !
226 !* cover classes
227 !
228 yrecfm='COVER_LIST'
229 ycomment='(LOGICAL LIST)'
230  CALL write_surf(dgu, u, &
231  hprogram,yrecfm,i%LCOVER(:),iresp,hcomment=ycomment,hdir='-')
232 !
233 ycomment='COVER FIELDS'
234  CALL write_surf_cov(dgu, u, &
235  hprogram,'COVER',i%XCOVER(:,:),i%LCOVER,iresp,hcomment=ycomment)
236 !
237 !* orography
238 !
239 yrecfm='ZS'
240 ycomment='ZS'
241  CALL write_surf(dgu, u, &
242  hprogram,yrecfm,i%XZS(:),iresp,hcomment=ycomment)
243 !
244 !* latitude, longitude
245 !
246  CALL write_grid(dgu, u, &
247  hprogram,ig%CGRID,ig%XGRID_PAR,ig%XLAT,ig%XLON,ig%XMESH_SIZE,iresp,i%XZ0EFFJPDIR)
248 !
249 !
250 !* clay fraction
251 !
252 !
253 yrecfm='CLAY'
254 ycomment='X_Y_CLAY'
255  CALL write_surf(dgu, u, &
256  hprogram,yrecfm,i%XCLAY(:,1),iresp,hcomment=ycomment)
257 !
258 !* sand fraction
259 !
260 yrecfm='SAND'
261 ycomment='X_Y_SAND'
262  CALL write_surf(dgu, u, &
263  hprogram,yrecfm,i%XSAND(:,1),iresp,hcomment=ycomment)
264 !
265 !* soil organic carbon
266 !
267 yrecfm='SOCP'
268 ycomment=''
269  CALL write_surf(dgu, u, &
270  hprogram,yrecfm,i%LSOCP,iresp,hcomment=ycomment)
271 !
272 IF(i%LSOCP)THEN
273  !
274  ycomment='X_Y_SOC'
275  yrecfm='SOC_TOP'
276  CALL write_surf(dgu, u, &
277  hprogram,yrecfm,i%XSOC(:,1),iresp,hcomment=ycomment)
278  yrecfm='SOC_SUB'
279  CALL write_surf(dgu, u, &
280  hprogram,yrecfm,i%XSOC(:,2),iresp,hcomment=ycomment)
281  !
282 ENDIF
283 !
284 !* permafrost distribution
285 !
286 yrecfm='PERMAFROST'
287 ycomment=''
288  CALL write_surf(dgu, u, &
289  hprogram,yrecfm,i%LPERM,iresp,hcomment=ycomment)
290 !
291 IF(i%LPERM)THEN
292  ycomment='X_Y_PERM'
293  yrecfm='PERM'
294  CALL write_surf(dgu, u, &
295  hprogram,yrecfm,i%XPERM(:),iresp,hcomment=ycomment)
296 ENDIF
297 !
298 !* groundwater distribution
299 !
300 yrecfm='GWKEY'
301 ycomment=''
302  CALL write_surf(dgu, u, &
303  hprogram,yrecfm,i%LGW,iresp,hcomment=ycomment)
304 !
305 IF(i%LGW)THEN
306  ycomment='X_Y_GWFRAC'
307  yrecfm='GWFRAC'
308  CALL write_surf(dgu, u, &
309  hprogram,yrecfm,i%XGW(:),iresp,hcomment=ycomment)
310 ENDIF
311 !
312 !SOILNOX
313 !
314 yrecfm='NO'
315 ycomment=''
316  CALL write_surf(dgu, u, &
317  hprogram,yrecfm,i%LNOF,iresp,hcomment=ycomment)
318 !
319 IF (i%LNOF) THEN
320  !
321  yrecfm='PH'
322  ycomment='X_Y_PH'
323  CALL write_surf(dgu, u, &
324  hprogram,yrecfm,i%XPH(:),iresp,hcomment=ycomment)
325  !
326  yrecfm='FERT'
327  ycomment='X_Y_FERT'
328  CALL write_surf(dgu, u, &
329  hprogram,yrecfm,i%XFERT(:),iresp,hcomment=ycomment)
330  !
331 ENDIF
332 !
333 !* subgrid-scale orography parameters to compute dynamical roughness length
334 !
335 yrecfm='AOSIP'
336 ycomment='X_Y_AOSIP'
337  CALL write_surf(dgu, u, &
338  hprogram,yrecfm,i%XAOSIP,iresp,hcomment=ycomment)
339 !
340 yrecfm='AOSIM'
341 ycomment='X_Y_AOSIM'
342  CALL write_surf(dgu, u, &
343  hprogram,yrecfm,i%XAOSIM,iresp,hcomment=ycomment)
344 !
345 yrecfm='AOSJP'
346 ycomment='X_Y_AOSJP'
347  CALL write_surf(dgu, u, &
348  hprogram,yrecfm,i%XAOSJP,iresp,hcomment=ycomment)
349 !
350 yrecfm='AOSJM'
351 ycomment='X_Y_AOSJM'
352  CALL write_surf(dgu, u, &
353  hprogram,yrecfm,i%XAOSJM,iresp,hcomment=ycomment)
354 !
355 yrecfm='HO2IP'
356 ycomment='X_Y_HO2IP'
357  CALL write_surf(dgu, u, &
358  hprogram,yrecfm,i%XHO2IP,iresp,hcomment=ycomment)
359 !
360 yrecfm='HO2IM'
361 ycomment='X_Y_HO2IM'
362  CALL write_surf(dgu, u, &
363  hprogram,yrecfm,i%XHO2IM,iresp,hcomment=ycomment)
364 !
365 yrecfm='HO2JP'
366 ycomment='X_Y_HO2JP'
367  CALL write_surf(dgu, u, &
368  hprogram,yrecfm,i%XHO2JP,iresp,hcomment=ycomment)
369 !
370 yrecfm='HO2JM'
371 ycomment='X_Y_HO2JM'
372  CALL write_surf(dgu, u, &
373  hprogram,yrecfm,i%XHO2JM,iresp,hcomment=ycomment)
374 !
375 yrecfm='SSO_SLOPE'
376 ycomment='X_Y_SSO_SLOPE (-)'
377  CALL write_surf(dgu, u, &
378  hprogram,yrecfm,i%XSSO_SLOPE,iresp,hcomment=ycomment)
379 !
380 !* orographic runoff coefficient
381 !
382 yrecfm='RUNOFFB'
383 ycomment='X_Y_RUNOFFB'
384  CALL write_surf(dgu, u, &
385  hprogram,yrecfm,i%XRUNOFFB,iresp,hcomment=ycomment)
386 !
387 !* subgrid drainage coefficient
388 !
389 yrecfm='WDRAIN'
390 ycomment='X_Y_WDRAIN'
391  CALL write_surf(dgu, u, &
392  hprogram,yrecfm,i%XWDRAIN,iresp,hcomment=ycomment)
393 !
394 !* topographic index statistics
395 !
396 yrecfm='CTI'
397 ycomment=''
398  CALL write_surf(dgu, u, &
399  hprogram,yrecfm,i%LCTI,iresp,hcomment=ycomment)
400 !
401 IF(i%LCTI)THEN
402 !
403 yrecfm='TI_MIN'
404 ycomment='X_Y_TI_MIN'
405  CALL write_surf(dgu, u, &
406  hprogram,yrecfm,i%XTI_MIN,iresp,hcomment=ycomment)
407 !
408 yrecfm='TI_MAX'
409 ycomment='X_Y_TI_MAX'
410  CALL write_surf(dgu, u, &
411  hprogram,yrecfm,i%XTI_MAX,iresp,hcomment=ycomment)
412 !
413 yrecfm='TI_MEAN'
414 ycomment='X_Y_TI_MEAN'
415  CALL write_surf(dgu, u, &
416  hprogram,yrecfm,i%XTI_MEAN,iresp,hcomment=ycomment)
417 !
418 yrecfm='TI_STD'
419 ycomment='X_Y_TI_STD'
420  CALL write_surf(dgu, u, &
421  hprogram,yrecfm,i%XTI_STD,iresp,hcomment=ycomment)
422 !
423 yrecfm='TI_SKEW'
424 ycomment='X_Y_TI_SKEW'
425  CALL write_surf(dgu, u, &
426  hprogram,yrecfm,i%XTI_SKEW,iresp,hcomment=ycomment)
427 !
428 ENDIF
429 !
430 !-------------------------------------------------------------------------------
431  CALL writesurf_pgd_isba_par_n(dgu, u, &
432  dti, &
433  hprogram)
434 IF (u%CNATURE=='TSZ0') CALL writesurf_pgd_tsz0_par_n(dgu, u, &
435  dtz, &
436  hprogram)
437 !
438 IF (lhook) CALL dr_hook('WRITESURF_PGD_ISBA_N',1,zhook_handle)
439 !-------------------------------------------------------------------------------
440 !
441 END SUBROUTINE writesurf_pgd_isba_n
subroutine writesurf_pgd_isba_n(DGU, DTI, DTZ, IG, I, U, HPROGRAM)
subroutine write_grid(DGU, U, HPROGRAM, HGRID, PGRID_PAR, PLAT, PLON, PMESH_SIZE, KRESP, PDIR, HDIR)
Definition: write_grid.F90:6
subroutine writesurf_pgd_isba_par_n(DGU, U, DTI, HPROGRAM)
subroutine, public write_surf_cov(DGU, U, HPROGRAM, HREC, PFIELD, OFLAG, KRESP, HCOMMENT, HDIR)
subroutine writesurf_pgd_tsz0_par_n(DGU, U, DTZ, HPROGRAM)