SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
write_diag_misc_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 write_diag_misc_isba_n (DTCO, DGU, U, DGI, DGMI, I, &
7  hprogram)
8 ! #################################
9 !
10 !!**** *WRITE_DIAG_MISC_ISBA* - writes the ISBA diagnostic fields
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !!
23 !! AUTHOR
24 !! ------
25 !! P. Le Moigne *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 10/2004
30 !! B. Decharme 2008 Total Albedo, Total SWI and Floodplains
31 !! B. Decharme 06/2009 key to write (or not) patch result
32 !! A.L. Gibelin 04/09 : Add respiration diagnostics
33 !! A.L. Gibelin 05/09 : Add carbon spinup
34 !! A.L. Gibelin 07/09 : Suppress RDK and transform GPP as a diagnostic
35 !! D. Carrer 04/11 : Add FAPAR and effective LAI
36 !! B. Decharme 09/2012 : suppress NWG_LAYER (parallelization problems)
37 !! B. Decharme 09/12 : Carbon fluxes in diag_evap
38 !! B. Decharme 09/12 New diag for DIF:
39 !! F2 stress
40 !! Root zone swi, wg and wgi
41 !! swi, wg and wgi comparable to ISBA-FR-DG2 and DG3 layers
42 !! active layer thickness over permafrost
43 !! frozen layer thickness over non-permafrost
44 !! B. Decharme 06/13 All snow outputs noted SN
45 !! XTSRAD_NAT instead of XAVG_TSRAD
46 !! delete NWG_SIZE
47 !! water table depth
48 !!
49 !-------------------------------------------------------------------------------
50 !
51 !* 0. DECLARATIONS
52 ! ------------
53 !
56 USE modd_surf_atm_n, ONLY : surf_atm_t
57 USE modd_diag_isba_n, ONLY : diag_isba_t
59 USE modd_isba_n, ONLY : isba_t
60 !
61 USE modd_surf_par, ONLY : nundef, xundef
62 !
63 USE modd_assim, ONLY : lassim, cassim_isba, nvar
64 !
65 USE modd_agri, ONLY : lagrip
66 !
67 USE modi_init_io_surf_n
69 USE modi_end_io_surf_n
70 !
71 USE yomhook ,ONLY : lhook, dr_hook
72 USE parkind1 ,ONLY : jprb
73 !
74 IMPLICIT NONE
75 !
76 !* 0.1 Declarations of arguments
77 ! -------------------------
78 !
79 !
80 TYPE(data_cover_t), INTENT(INOUT) :: dtco
81 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
82 TYPE(surf_atm_t), INTENT(INOUT) :: u
83 TYPE(diag_isba_t), INTENT(INOUT) :: dgi
84 TYPE(diag_misc_isba_t), INTENT(INOUT) :: dgmi
85 TYPE(isba_t), INTENT(INOUT) :: i
86 !
87  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
88 !
89 !* 0.2 Declarations of local variables
90 ! -------------------------------
91 !
92 INTEGER :: iresp ! IRESP : return-code if a problem appears
93  CHARACTER(LEN=1) :: yvar
94  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
95  CHARACTER(LEN=100):: ycomment ! Comment string
96  CHARACTER(LEN=2) :: ylvl
97  CHARACTER(LEN=20) :: yform
98 !
99 INTEGER :: jlayer, jj, idepth, jvar
100 !
101 REAL(KIND=JPRB) :: zhook_handle
102 !
103 !-------------------------------------------------------------------------------
104 !
105 ! Initialisation for IO
106 !
107 IF (lhook) CALL dr_hook('WRITE_DIAG_MISC_ISBA_N',0,zhook_handle)
108  CALL init_io_surf_n(dtco, dgu, u, &
109  hprogram,'NATURE','ISBA ','WRITE')
110 !
111 !-------------------------------------------------------------------------------
112 !
113 IF (dgmi%LSURF_MISC_BUDGET) THEN
114  !
115  !* 2. Miscellaneous fields :
116  !
117  !-------------------------------------------------------------------------------
118  !
119  ! 2.1 Halstead coefficient
120  ! --------------------
121  !
122  yrecfm='HV_ISBA'
123  ycomment='Halstead coefficient averaged over tile nature (-)'
124  CALL write_surf(dgu, u, &
125  hprogram,yrecfm,dgmi%XAVG_HV(:),iresp,hcomment=ycomment)
126  !
127  ! 2.2 Snow fractions
128  ! --------------
129  !
130  yrecfm='PSNG_ISBA'
131  ycomment='snow fraction over ground averaged over tile nature (-)'
132  CALL write_surf(dgu, u, &
133  hprogram,yrecfm,dgmi%XAVG_PSNG(:),iresp,hcomment=ycomment)
134  !
135  yrecfm='PSNV_ISBA'
136  ycomment='snow fraction over vegetation averaged over tile nature (-)'
137  CALL write_surf(dgu, u, &
138  hprogram,yrecfm,dgmi%XAVG_PSNV(:),iresp,hcomment=ycomment)
139  !
140  yrecfm='PSN_ISBA'
141  ycomment='total snow fraction averaged over tile nature (-)'
142  CALL write_surf(dgu, u, &
143  hprogram,yrecfm,dgmi%XAVG_PSN(:),iresp,hcomment=ycomment)
144  !
145  ! 2.3 Total Albedo and surface temperature
146  ! ------------------------------------
147  !
148  yrecfm='TALB_ISBA'
149  ycomment='total albedo over tile nature (-)'
150  CALL write_surf(dgu, u, &
151  hprogram,yrecfm,dgmi%XAVG_ALBT(:),iresp,hcomment=ycomment)
152  !
153  IF (i%TSNOW%SCHEME=='3-L' .OR. i%TSNOW%SCHEME=='CRO') THEN
154  !
155  yrecfm='TS_ISBA'
156  ycomment='total surface temperature (isba+snow) over tile nature'
157  CALL write_surf(dgu, u, &
158  hprogram,yrecfm,dgi%XAVG_TS(:),iresp,hcomment=ycomment)
159  !
160  yrecfm='TSRAD_ISBA'
161  ycomment='total radiative surface temperature (isba+snow) over tile nature'
162  CALL write_surf(dgu, u, &
163  hprogram,yrecfm,i%XTSRAD_NAT(:),iresp,hcomment=ycomment)
164  !
165  END IF
166  !
167  ! 2.4 Soil Wetness Index, Water content and active layer depth
168  ! --------------------------------------------------------
169  !
170  IF(i%CISBA=='DIF')THEN
171  DO jlayer = 1,i%NGROUND_LAYER
172  DO jj=1,SIZE(i%NWG_LAYER,1)
173  idepth=maxval(i%NWG_LAYER(jj,:),i%NWG_LAYER(jj,:)/=nundef)
174  IF(jlayer>idepth)THEN
175  dgmi%XAVG_SWI (jj,jlayer) = xundef
176  dgmi%XAVG_TSWI(jj,jlayer) = xundef
177  ENDIF
178  ENDDO
179  ENDDO
180  ENDIF
181  !
182  DO jlayer=1,i%NGROUND_LAYER
183  !
184  WRITE(ylvl,'(I2)') jlayer
185  !
186  yrecfm='SWI'//adjustl(ylvl(:len_trim(ylvl)))
187  yrecfm=yrecfm(:len_trim(yrecfm))//'_ISBA'
188  yform='(A29,I1.1,A4)'
189  IF (jlayer >= 10) yform='(A29,I2.2,A4)'
190  WRITE(ycomment,fmt=yform) 'soil wetness index for layer ',jlayer,' (-)'
191  CALL write_surf(dgu, u, &
192  hprogram,yrecfm,dgmi%XAVG_SWI(:,jlayer),iresp,hcomment=ycomment)
193  !
194  yrecfm='TSWI'//adjustl(ylvl(:len_trim(ylvl)))
195  yrecfm=yrecfm(:len_trim(yrecfm))//'_ISBA'
196  yform='(A29,I1.1,A4)'
197  IF (jlayer >= 10) yform='(A29,I2.2,A4)'
198  WRITE(ycomment,fmt=yform) 'total swi (liquid+solid) for layer ',jlayer,' (-)'
199  CALL write_surf(dgu, u, &
200  hprogram,yrecfm,dgmi%XAVG_TSWI(:,jlayer),iresp,hcomment=ycomment)
201  !
202  END DO
203  !
204  yrecfm='SWI_T_ISBA'
205  ycomment='soil wetness index over the soil column (-)'
206  CALL write_surf(dgu, u, &
207  hprogram,yrecfm,dgmi%XSOIL_SWI(:),iresp,hcomment=ycomment)
208  !
209  yrecfm='TSWI_T_ISBA'
210  ycomment='total soil wetness index over the soil column (-)'
211  CALL write_surf(dgu, u, &
212  hprogram,yrecfm,dgmi%XSOIL_TSWI(:),iresp,hcomment=ycomment)
213  !
214  yrecfm='WGTOT_T_ISBA'
215  ycomment='total water content (liquid+solid) over the soil column (kg/m2)'
216  CALL write_surf(dgu, u, &
217  hprogram,yrecfm,dgmi%XSOIL_TWG(:),iresp,hcomment=ycomment)
218  !
219  yrecfm='WGI_T_ISBA'
220  ycomment='total ice content (solid) over the soil column (kg/m2)'
221  CALL write_surf(dgu, u, &
222  hprogram,yrecfm,dgmi%XSOIL_TWGI(:),iresp,hcomment=ycomment)
223  !
224  yrecfm='WGTOT_ISBA'
225  ycomment='total volumetric water content (liquid+solid) over the soil column (m3/m3)'
226  CALL write_surf(dgu, u, &
227  hprogram,yrecfm,dgmi%XSOIL_WG(:),iresp,hcomment=ycomment)
228  !
229  yrecfm='WGI_ISBA'
230  ycomment='total volumetric ice content (solid) over the soil column (m3/m3)'
231  CALL write_surf(dgu, u, &
232  hprogram,yrecfm,dgmi%XSOIL_WGI(:),iresp,hcomment=ycomment)
233  !
234  IF(i%CISBA=='DIF') THEN
235  !
236  IF (dgmi%LSURF_MISC_DIF)THEN
237  !
238  yrecfm='TSWI_D2_ISBA'
239  ycomment='total soil wetness index over comparable FR-DG2 reservoir (-)'
240  CALL write_surf(dgu, u, &
241  hprogram,yrecfm,dgmi%XFRD2_TSWI(:),iresp,hcomment=ycomment)
242  !
243  yrecfm='WG_D2_ISBA'
244  ycomment='liquid water content over comparable FR-DG2 reservoir (m3/m3)'
245  CALL write_surf(dgu, u, &
246  hprogram,yrecfm,dgmi%XFRD2_TWG(:),iresp,hcomment=ycomment)
247  !
248  yrecfm='WGI_D2_ISBA'
249  ycomment='ice content over comparable FR-DG2 reservoir (m3/m3)'
250  CALL write_surf(dgu, u, &
251  hprogram,yrecfm,dgmi%XFRD2_TWGI(:),iresp,hcomment=ycomment)
252  !
253  yrecfm='TSWI_D3_ISBA'
254  ycomment='total soil wetness index over comparable FR-DG3 reservoir (-)'
255  CALL write_surf(dgu, u, &
256  hprogram,yrecfm,dgmi%XFRD3_TSWI(:),iresp,hcomment=ycomment)
257  !
258  yrecfm='WG_D3_ISBA'
259  ycomment='liquid water content over comparable FR-DG3 reservoir (m3/m3)'
260  CALL write_surf(dgu, u, &
261  hprogram,yrecfm,dgmi%XFRD3_TWG(:),iresp,hcomment=ycomment)
262  !
263  yrecfm='WGI_D3_ISBA'
264  ycomment='ice content over comparable FR-DG3 reservoir (m3/m3)'
265  CALL write_surf(dgu, u, &
266  hprogram,yrecfm,dgmi%XFRD3_TWGI(:),iresp,hcomment=ycomment)
267  !
268  ENDIF
269  !
270  yrecfm='ALT_ISBA'
271  ycomment='active layer thickness over permafrost (m)'
272  CALL write_surf(dgu, u, &
273  hprogram,yrecfm,dgmi%XAVG_ALT(:),iresp,hcomment=ycomment)
274  !
275  yrecfm='FLT_ISBA'
276  ycomment='frozen layer thickness over non-permafrost (m)'
277  CALL write_surf(dgu, u, &
278  hprogram,yrecfm,dgmi%XAVG_FLT(:),iresp,hcomment=ycomment)
279  !
280  ENDIF
281  !
282  ! 2.5 Snow outputs
283  ! -------------
284  !
285  yrecfm='WSN_T_ISBA'
286  ycomment='Total_snow_reservoir (kg/m2)'
287  CALL write_surf(dgu, u, &
288  hprogram,yrecfm,dgmi%XAVG_TWSNOW(:),iresp,hcomment=ycomment)
289  !
290  yrecfm='DSN_T_ISBA'
291  ycomment='Total_snow_depth (m)'
292  CALL write_surf(dgu, u, &
293  hprogram,yrecfm,dgmi%XAVG_TDSNOW(:),iresp,hcomment=ycomment)
294  !
295  yrecfm='TSN_T_ISBA'
296  ycomment='Total_snow_temperature (K)'
297  CALL write_surf(dgu, u, &
298  hprogram,yrecfm,dgmi%XAVG_TTSNOW(:),iresp,hcomment=ycomment)
299  !
300  ! 2.6 SGH scheme
301  ! ----------
302  !
303  IF(i%CRUNOFF=='SGH '.OR.i%CRUNOFF=='DT92')THEN
304  yrecfm='FSAT_ISBA'
305  ycomment='Soil saturated fraction (-)'
306  CALL write_surf(dgu, u, &
307  hprogram,yrecfm,dgmi%XAVG_FSAT(:),iresp,hcomment=ycomment)
308  ENDIF
309  !
310  IF(i%CRAIN=='SGH ')THEN
311  yrecfm='MUF_ISBA'
312  ycomment='fraction of the grid cell reached by the rainfall (-)'
313  CALL write_surf(dgu, u, &
314  hprogram,yrecfm,i%XMUF(:),iresp,hcomment=ycomment)
315  ENDIF
316  !
317  ! 2.7 Flooding scheme
318  ! ---------------
319  !
320  IF(i%LFLOOD)THEN
321  !
322  yrecfm='FFG_ISBA'
323  ycomment='flood fraction over ground averaged over tile nature (-)'
324  CALL write_surf(dgu, u, &
325  hprogram,yrecfm,dgmi%XAVG_FFG(:),iresp,hcomment=ycomment)
326  !
327  yrecfm='FFV_ISBA'
328  ycomment='flood fraction over vegetation averaged over tile nature (-)'
329  CALL write_surf(dgu, u, &
330  hprogram,yrecfm,dgmi%XAVG_FFV(:),iresp,hcomment=ycomment)
331  !
332  yrecfm='FF_ISBA'
333  ycomment='total flood fraction averaged over tile nature (-)'
334  CALL write_surf(dgu, u, &
335  hprogram,yrecfm,dgmi%XAVG_FF(:),iresp,hcomment=ycomment)
336  !
337  yrecfm='FFLOOD_ISBA'
338  ycomment='Grdi-cell potential flood fraction (-)'
339  CALL write_surf(dgu, u, &
340  hprogram,yrecfm,i%XFFLOOD(:),iresp,hcomment=ycomment)
341  !
342  yrecfm='PIFLOOD_ISBA'
343  ycomment='Grdi-cell Potential_floodplain_infiltration (kg/m2/s)'
344  CALL write_surf(dgu, u, &
345  hprogram,yrecfm,i%XPIFLOOD(:),iresp,hcomment=ycomment)
346  !
347  ENDIF
348  !
349  ! 2.8 Total LAI
350  ! ---------
351  !
352  IF(i%CPHOTO/='NON'.OR.i%NPATCH>1)THEN
353  yrecfm='LAI_ISBA'
354  ycomment='leaf area index (m2/m2)'
355  CALL write_surf(dgu, u, &
356  hprogram,yrecfm,dgmi%XAVG_LAI(:),iresp,hcomment=ycomment)
357  ENDIF
358  !
359  ! 2.9 Water table depth
360  ! -----------------
361  !
362  IF(i%LWTD)THEN
363  !
364  yrecfm='FWTD_ISBA'
365  ycomment='grid-cell fraction of water table to rise'
366  CALL write_surf(dgu, u, &
367  hprogram,yrecfm,i%XFWTD(:),iresp,hcomment=ycomment)
368  !
369  yrecfm='WTD_ISBA'
370  ycomment='water table depth from RRM model or observation (m)'
371  CALL write_surf(dgu, u, &
372  hprogram,yrecfm,i%XWTD(:),iresp,hcomment=ycomment)
373  !
374  ENDIF
375  !* 3. Miscellaneous fields for each patch :
376  ! -------------------------------------
377  !
378  !----------------------------------------------------------------------------
379  !User wants (or not) patch output
380  IF(dgi%LPATCH_BUDGET)THEN
381  !----------------------------------------------------------------------------
382  !
383  ! 3.1 Soil Wetness Index and active layer depth
384  ! -----------------------------------------
385  !
386  DO jlayer=1,i%NGROUND_LAYER
387  !
388  WRITE(ylvl,'(I2)') jlayer
389  !
390  yrecfm='SWI'//adjustl(ylvl(:len_trim(ylvl)))
391  yform='(A39,I1.1,A4)'
392  IF (jlayer >= 10) yform='(A39,I2.2,A4)'
393  WRITE(ycomment,fmt=yform) 'soil wetness index per patch for layer ',jlayer,' (-)'
394  CALL write_surf(dgu, u, &
395  hprogram,yrecfm,dgmi%XSWI(:,jlayer,:),iresp,hcomment=ycomment)
396  !
397  yrecfm='TSWI'//adjustl(ylvl(:len_trim(ylvl)))
398  yform='(A39,I1.1,A4)'
399  IF (jlayer >= 10) yform='(A39,I2.2,A4)'
400  WRITE(ycomment,fmt=yform) 'total swi (liquid+solid) per patch for layer ',jlayer,' (-)'
401  CALL write_surf(dgu, u, &
402  hprogram,yrecfm,dgmi%XTSWI(:,jlayer,:),iresp,hcomment=ycomment)
403  !
404  END DO
405  !
406  IF(i%CISBA=='DIF')THEN
407  !
408  yrecfm='ALT_P'
409  ycomment='active layer thickness over permafrost per patch (m)'
410  CALL write_surf(dgu, u, &
411  hprogram,yrecfm,dgmi%XALT(:,:),iresp,hcomment=ycomment)
412  !
413  yrecfm='FLT_P'
414  ycomment='frozen layer thickness over non-permafrost per patch (m)'
415  CALL write_surf(dgu, u, &
416  hprogram,yrecfm,dgmi%XFLT(:,:),iresp,hcomment=ycomment)
417  !
418  ENDIF
419  !
420  ! 3.2 Snow fractions
421  ! --------------
422  !
423  yrecfm='PSNG_P'
424  ycomment='snow fraction per patch over ground '
425  CALL write_surf(dgu, u, &
426  hprogram,yrecfm,dgmi%XDPSNG(:,:),iresp,hcomment=ycomment)
427  !
428  yrecfm='PSNV_P'
429  ycomment='snow fraction per patch over vegetation'
430  CALL write_surf(dgu, u, &
431  hprogram,yrecfm,dgmi%XDPSNV(:,:),iresp,hcomment=ycomment)
432  !
433  yrecfm='PSN_P'
434  ycomment='total snow fraction per patch'
435  CALL write_surf(dgu, u, &
436  hprogram,yrecfm,dgmi%XDPSN(:,:),iresp,hcomment=ycomment)
437  !
438  ! 3.3 SGH scheme
439  ! ----------
440  !
441  IF(i%CRUNOFF=='DT92')THEN
442  yrecfm='FSAT_P'
443  ycomment='Soil saturated fraction per patch (-)'
444  CALL write_surf(dgu, u, &
445  hprogram,yrecfm,dgmi%XDFSAT(:,:),iresp,hcomment=ycomment)
446  ENDIF
447  !
448  ! 3.3 Flood fractions
449  ! --------------
450  !
451  IF(i%LFLOOD)THEN
452  !
453  yrecfm='FFG_P'
454  ycomment='flood fraction per patch over ground '
455  CALL write_surf(dgu, u, &
456  hprogram,yrecfm,dgmi%XDFFG(:,:),iresp,hcomment=ycomment)
457  !
458  yrecfm='FFV_P'
459  ycomment='flood fraction per patch over vegetation'
460  CALL write_surf(dgu, u, &
461  hprogram,yrecfm,dgmi%XDFFV(:,:),iresp,hcomment=ycomment)
462  !
463  yrecfm='FF_P'
464  ycomment='total flood fraction per patch'
465  CALL write_surf(dgu, u, &
466  hprogram,yrecfm,dgmi%XDFF(:,:),iresp,hcomment=ycomment)
467  !
468  ENDIF
469  !
470  ! 3.4 Total Albedo
471  ! ------------
472  !
473  yrecfm='TALB'
474  ycomment='total albedo per patch'
475  !
476  CALL write_surf(dgu, u, &
477  hprogram,yrecfm,dgmi%XALBT(:,:),iresp,hcomment=ycomment)
478  !
479  IF (i%TSNOW%SCHEME=='3-L' .OR. i%TSNOW%SCHEME=='CRO') THEN
480  yrecfm='TS_P'
481  ycomment='total surface temperature (isba+snow) per patch'
482  CALL write_surf(dgu, u, &
483  hprogram,yrecfm,dgi%XTS(:,:),iresp,hcomment=ycomment)
484  yrecfm='TSRAD_P'
485  ycomment='total radiative surface temperature (isba+snow) per patch'
486  CALL write_surf(dgu, u, &
487  hprogram,yrecfm,dgi%XTSRAD(:,:),iresp,hcomment=ycomment)
488  ENDIF
489  !
490  ! 3.5 Halstead coefficient
491  ! --------------------
492  !
493  yrecfm='HV'
494  ycomment='Halstead coefficient per patch'
495  CALL write_surf(dgu, u, &
496  hprogram,yrecfm,dgmi%XHV(:,:),iresp,hcomment=ycomment)
497  !
498  ! 3.6 Snow outputs
499  ! -----------------
500  !
501  yrecfm='WSN_T_P'
502  ycomment='X_Y_WSNOW_TOT (kg/m2) per patch'
503  CALL write_surf(dgu, u, &
504  hprogram,yrecfm,dgmi%XTWSNOW(:,:),iresp,hcomment=ycomment)
505  !
506  yrecfm='DSN_T_P'
507  ycomment='X_Y_DSNOW_TOT (m) per patch'
508  CALL write_surf(dgu, u, &
509  hprogram,yrecfm,dgmi%XTDSNOW(:,:),iresp,hcomment=ycomment)
510  !
511  yrecfm='TSN_T_P'
512  ycomment='X_Y_TSNOW_TOT (k) per patch'
513  CALL write_surf(dgu, u, &
514  hprogram,yrecfm,dgmi%XTTSNOW(:,:),iresp,hcomment=ycomment)
515  !
516  IF (i%TSNOW%SCHEME=='3-L' .OR. i%TSNOW%SCHEME=='CRO') THEN
517  !
518  DO jlayer=1,i%TSNOW%NLAYER
519  !
520  WRITE(ylvl,'(I2)') jlayer
521  !
522  yrecfm='SNOWLIQ'//adjustl(ylvl(:len_trim(ylvl)))
523  yform='(A17,I1.1,A4)'
524  IF (jlayer >= 10) yform='(A17,I2.2,A4)'
525  WRITE(ycomment,fmt=yform) 'snow liquid water',jlayer,' (m)'
526  CALL write_surf(dgu, u, &
527  hprogram,yrecfm,dgmi%XSNOWLIQ(:,jlayer,:),iresp,hcomment=ycomment)
528  !
529  yrecfm='SNOWTEMP'//adjustl(ylvl(:len_trim(ylvl)))
530  yform='(A16,I1.1,A4)'
531  IF (jlayer >= 10) yform='(A16,I2.2,A4)'
532  WRITE(ycomment,fmt=yform) 'snow temperature',jlayer,' (K)'
533  CALL write_surf(dgu, u, &
534  hprogram,yrecfm,dgmi%XSNOWTEMP(:,jlayer,:),iresp,hcomment=ycomment)
535  !
536  END DO
537  !
538  ENDIF
539  !
540  END IF
541  !
542  IF (lagrip) THEN
543  !
544  ! 2.8 Irrigation threshold
545  ! --------------------
546  !
547  yrecfm='IRRISEUIL'
548  ycomment='irrigation threshold per patch'
549  CALL write_surf(dgu, u, &
550  hprogram,yrecfm,dgmi%XSEUIL(:,:),iresp,hcomment=ycomment)
551  !
552  ENDIF
553  !
554  IF (i%LTR_ML) THEN
555  !
556  yrecfm='FAPAR'
557  ycomment='FAPAR (-)'
558  CALL write_surf(dgu, u, &
559  hprogram,yrecfm,dgmi%XFAPAR(:,:),iresp,hcomment=ycomment)
560  !
561  yrecfm='FAPIR'
562  ycomment='FAPIR (-)'
563  CALL write_surf(dgu, u, &
564  hprogram,yrecfm,dgmi%XFAPIR(:,:),iresp,hcomment=ycomment)
565  !
566  yrecfm='FAPAR_BS'
567  ycomment='FAPAR_BS (-)'
568  CALL write_surf(dgu, u, &
569  hprogram,yrecfm,dgmi%XFAPAR_BS(:,:),iresp,hcomment=ycomment)
570  !
571  yrecfm='FAPIR_BS'
572  ycomment='FAPIR_BS (-)'
573  CALL write_surf(dgu, u, &
574  hprogram,yrecfm,dgmi%XFAPIR_BS(:,:),iresp,hcomment=ycomment)
575  !
576  yrecfm='DFAPARC'
577  ycomment='DFAPARC (-)'
578  CALL write_surf(dgu, u, &
579  hprogram,yrecfm,dgmi%XDFAPARC(:,:),iresp,hcomment=ycomment)
580  !
581  yrecfm='DFAPIRC'
582  ycomment='DFAPIRC (-)'
583  CALL write_surf(dgu, u, &
584  hprogram,yrecfm,dgmi%XDFAPIRC(:,:),iresp,hcomment=ycomment)
585  !
586  yrecfm='DLAI_EFFC'
587  ycomment='DLAI_EFFC (m2/m2)'
588  CALL write_surf(dgu, u, &
589  hprogram,yrecfm,dgmi%XDLAI_EFFC(:,:),iresp,hcomment=ycomment)
590  !
591  ENDIF
592  !
593  IF (lassim .AND. cassim_isba=="EKF ") THEN
594  !
595  DO jvar = 1,nvar
596  WRITE(yvar,fmt='(I1.1)') jvar
597  yrecfm="ANAL_INCR"//yvar
598  ycomment="by patch"
599  CALL write_surf(dgu, u, &
600  hprogram,yrecfm,i%XINCR(:,i%NPATCH*(jvar-1)+1:i%NPATCH*jvar),iresp,hcomment=ycomment)
601  ENDDO
602  !
603  ENDIF
604  !
605 ENDIF
606 ! End of IO
607 !
608  CALL end_io_surf_n(hprogram)
609 IF (lhook) CALL dr_hook('WRITE_DIAG_MISC_ISBA_N',1,zhook_handle)
610 !
611 END SUBROUTINE write_diag_misc_isba_n
subroutine init_io_surf_n(DTCO, DGU, U, HPROGRAM, HMASK, HSCHEME, HACTION)
subroutine write_diag_misc_isba_n(DTCO, DGU, U, DGI, DGMI, I, HPROGRAM)
subroutine end_io_surf_n(HPROGRAM)
Definition: end_io_surfn.F90:6