SURFEX v8.1
General documentation of Surfex
write_diag_seb_tebn.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_seb_teb_n (DTCO, HSELECT, U, CHT, DGO, D, DUT, HPROGRAM)
7 ! #################################
8 !
9 !!**** *WRITE_DIAG_SEB_TEB_n* - writes TEB diagnostics
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !!
23 !! AUTHOR
24 !! ------
25 !! V. Masson *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 01/2004
30 !! Modified 01/2006 : TEB flux parameterization.
31 !! V. Masson 10/2013 : Adds heat/cold stress ranges diagnostics
32 !! B. Decharme 02/2016 : NBLOCK instead of LCOUNTW for compilation in AAA
33 !-------------------------------------------------------------------------------
34 !
35 !* 0. DECLARATIONS
36 ! ------------
37 !
38 !
41 USE modd_surf_atm_n, ONLY : surf_atm_t
42 USE modd_ch_teb_n, ONLY : ch_teb_t
44 !
46 !
47 USE modd_surf_par, ONLY : xundef
48 USE modd_utci
49 !
50 #ifdef SFX_ARO
51 USE modd_io_surf_aro, ONLY : nblock
52 #endif
53 !
54 #ifdef SFX_OL
55 USE modd_io_surf_ol, ONLY : ldef
56 #endif
57 !
58 USE modi_init_io_surf_n
60 USE modi_end_io_surf_n
61 !
62 USE yomhook ,ONLY : lhook, dr_hook
63 USE parkind1 ,ONLY : jprb
64 !
65 IMPLICIT NONE
66 !
67 !* 0.1 Declarations of arguments
68 ! -------------------------
69 !
70 !
71 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
72  CHARACTER(LEN=*), DIMENSION(:), INTENT(IN) :: HSELECT
73 TYPE(surf_atm_t), INTENT(INOUT) :: U
74 TYPE(ch_teb_t), INTENT(INOUT) :: CHT
75 TYPE(diag_options_t), INTENT(INOUT) :: DGO
76 TYPE(diag_t), INTENT(INOUT) :: D
77 TYPE(diag_utci_teb_t), INTENT(INOUT) :: DUT
78 !
79  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling
80 !
81 !* 0.2 Declarations of local variables
82 ! -------------------------------
83 !
84 INTEGER :: IRESP ! IRESP : return-code if a problem appears
85  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
86  CHARACTER(LEN=100):: YCOMMENT ! Comment string
87  CHARACTER(LEN=2) :: YNUM
88 !
89 LOGICAL :: GRESET
90 INTEGER :: JSV, JSW
91 INTEGER :: JSTRESS ! loop on heat stress ranges
92 REAL(KIND=JPRB) :: ZHOOK_HANDLE
93 !-------------------------------------------------------------------------------
94 !
95 ! Initialisation for IO
96 !
97 IF (lhook) CALL dr_hook('WRITE_DIAG_SEB_TEB_N',0,zhook_handle)
98 !
99 greset=.true.
100 #ifdef SFX_ARO
101 greset=(nblock>0)
102 #endif
103 #ifdef SFX_OL
104 IF (ldef) greset = .false.
105 #endif
106 !
107  CALL init_io_surf_n(dtco, u, hprogram,'TOWN ','TEB ','WRITE','TEB_DIAGNOSTICS.OUT.nc')
108 !
109 !
110 !
111 !* 2. Richardson number :
112 ! -----------------
113 !
114 IF (dgo%N2M>=1) THEN
115 
116  yrecfm='RI_TEB'
117  ycomment='X_Y_'//yrecfm
118  CALL write_surf(hselect,hprogram,yrecfm,d%XRI(:),iresp,hcomment=ycomment)
119  !
120 END IF
121 !
122 !* 3. Energy fluxes :
123 ! -------------
124 !
125 IF (dgo%LSURF_BUDGET) THEN
126 
127  yrecfm='RN_TEB'
128  ycomment='X_Y_'//yrecfm//' (W/m2)'
129  CALL write_surf(hselect,hprogram,yrecfm,d%XRN(:),iresp,hcomment=ycomment)
130  !
131  yrecfm='H_TEB'
132  ycomment='X_Y_'//yrecfm//' (W/m2)'
133  CALL write_surf(hselect,hprogram,yrecfm,d%XH(:),iresp,hcomment=ycomment)
134  !
135  yrecfm='LE_TEB'
136  ycomment='X_Y_'//yrecfm//' (W/m2)'
137  CALL write_surf(hselect,hprogram,yrecfm,d%XLE(:),iresp,hcomment=ycomment)
138  !
139  yrecfm='GFLUX_TEB'
140  ycomment='X_Y_'//yrecfm//' (W/m2)'
141  CALL write_surf(hselect,hprogram,yrecfm,d%XGFLUX(:),iresp,hcomment=ycomment)
142  !
143  IF (dgo%LRAD_BUDGET) THEN
144  !
145  yrecfm='SWD_TEB'
146  ycomment='X_Y_'//yrecfm//' (W/m2)'
147  CALL write_surf(hselect,hprogram,yrecfm,d%XSWD(:),iresp,hcomment=ycomment)
148  !
149  yrecfm='SWU_TEB'
150  ycomment='X_Y_'//yrecfm//' (W/m2)'
151  CALL write_surf(hselect,hprogram,yrecfm,d%XSWU(:),iresp,hcomment=ycomment)
152  !
153  yrecfm='LWD_TEB'
154  ycomment='X_Y_'//yrecfm//' (W/m2)'
155  CALL write_surf(hselect,hprogram,yrecfm,d%XLWD(:),iresp,hcomment=ycomment)
156  !
157  yrecfm='LWU_TEB'
158  ycomment='X_Y_'//yrecfm//' (W/m2)'
159  CALL write_surf(hselect,hprogram,yrecfm,d%XLWU(:),iresp,hcomment=ycomment)
160  !
161  IF (lallow_add_dim) THEN
162  !
163  yrecfm='SWD_TEB'
164  ycomment='X_Y_'//yrecfm//' (W/m2)'
165  CALL write_surf(hselect,&
166  hprogram,yrecfm,d%XSWBD(:,:),iresp,hcomment=ycomment, hnam_dim=yswband_dim_name)
167  !
168  yrecfm='SWU_TEB'
169  ycomment='X_Y_'//yrecfm//' (W/m2)'
170  CALL write_surf(hselect,&
171  hprogram,yrecfm,d%XSWBD(:,:),iresp,hcomment=ycomment, hnam_dim=yswband_dim_name)
172  !
173  ELSE
174  !
175  DO jsw=1, SIZE(d%XSWBD,2)
176  ynum=achar(48+jsw)
177  !
178  yrecfm='SWD_TEB_'//ynum
179  ycomment='X_Y_'//yrecfm//' (W/m2)'
180  CALL write_surf(hselect,hprogram,yrecfm,d%XSWBD(:,jsw),iresp,hcomment=ycomment)
181  !
182  yrecfm='SWU_TEB_'//ynum
183  ycomment='X_Y_'//yrecfm//' (W/m2)'
184  CALL write_surf(hselect,hprogram,yrecfm,d%XSWBU(:,jsw),iresp,hcomment=ycomment)
185  !
186  ENDDO
187  !
188  ENDIF
189  !
190  ENDIF
191  !
192  yrecfm='FMU_TEB'
193  ycomment='X_Y_'//yrecfm//' (kg/ms2)'
194  CALL write_surf(hselect,hprogram,yrecfm,d%XFMU(:),iresp,hcomment=ycomment)
195  !
196  yrecfm='FMV_TEB'
197  ycomment='X_Y_'//yrecfm//' (kg/ms2)'
198  CALL write_surf(hselect,hprogram,yrecfm,d%XFMV(:),iresp,hcomment=ycomment)
199  !
200 END IF
201 !
202 !
203 !
204 !* 4. Transfer coefficients
205 ! ---------------------
206 !
207 IF (dgo%LCOEF) THEN
208 
209  yrecfm='CD_TEB'
210  ycomment='X_Y_'//yrecfm
211  CALL write_surf(hselect,hprogram,yrecfm,d%XCD(:),iresp,hcomment=ycomment)
212  !
213  yrecfm='CH_TEB'
214  ycomment='X_Y_'//yrecfm
215  CALL write_surf(hselect,hprogram,yrecfm,d%XCH(:),iresp,hcomment=ycomment)
216  !
217  yrecfm='CE_TEB'
218  ycomment='X_Y_'//yrecfm
219  CALL write_surf(hselect,hprogram,yrecfm,d%XCE(:),iresp,hcomment=ycomment)
220  !
221  yrecfm='Z0_TEB'
222  ycomment='X_Y_'//yrecfm//' (M)'
223  CALL write_surf(hselect,hprogram,yrecfm,d%XZ0(:),iresp,hcomment=ycomment)
224  !
225  yrecfm='Z0H_TEB'
226  ycomment='X_Y_'//yrecfm//' (M)'
227  CALL write_surf(hselect,hprogram,yrecfm,d%XZ0H(:),iresp,hcomment=ycomment)
228  !
229 ENDIF
230 !
231 !
232 !* 5. Surface humidity
233 ! ----------------
234 !
235 IF (dgo%LSURF_VARS) THEN
236 
237  yrecfm='QS_TEB'
238  ycomment='X_Y_'//yrecfm//' (KG/KG)'
239  CALL write_surf(hselect,hprogram,yrecfm,d%XQS(:),iresp,hcomment=ycomment)
240  !
241 ENDIF
242 
243 !
244 !* 5. parameters at 2 and 10 meters :
245 ! -----------------------------
246 !
247 IF (dgo%N2M>=1) THEN
248 
249  yrecfm='T2M_TEB'
250  ycomment='X_Y_'//yrecfm//' (K)'
251  CALL write_surf(hselect,hprogram,yrecfm,d%XT2M(:),iresp,hcomment=ycomment)
252  !
253  yrecfm='T2MMIN_TEB'
254  ycomment='X_Y_'//yrecfm//' (K)'
255  CALL write_surf(hselect,hprogram,yrecfm,d%XT2M_MIN(:),iresp,hcomment=ycomment)
256  IF(greset)d%XT2M_MIN(:)=xundef
257  !
258  yrecfm='T2MMAX_TEB'
259  ycomment='X_Y_'//yrecfm//' (K)'
260  CALL write_surf(hselect,hprogram,yrecfm,d%XT2M_MAX(:),iresp,hcomment=ycomment)
261  IF(greset)d%XT2M_MAX(:)=-xundef
262  !
263  yrecfm='Q2M_TEB'
264  ycomment='X_Y_'//yrecfm//' (KG/KG)'
265  CALL write_surf(hselect,hprogram,yrecfm,d%XQ2M(:),iresp,hcomment=ycomment)
266  !
267  yrecfm='HU2M_TEB'
268  ycomment='X_Y_'//yrecfm//' (KG/KG)'
269  CALL write_surf(hselect,hprogram,yrecfm,d%XHU2M(:),iresp,hcomment=ycomment)
270  !
271  yrecfm='HU2MMIN_TEB'
272  ycomment='X_Y_'//yrecfm//' (-)'
273  CALL write_surf(hselect,hprogram,yrecfm,d%XHU2M_MIN(:),iresp,hcomment=ycomment)
274  IF(greset)d%XHU2M_MIN(:)=xundef
275  !
276  yrecfm='HU2MMAX_TEB'
277  ycomment='X_Y_'//yrecfm//' (-)'
278  CALL write_surf(hselect,hprogram,yrecfm,d%XHU2M_MAX(:),iresp,hcomment=ycomment)
279  IF(greset)d%XHU2M_MAX(:)=-xundef
280  !
281  yrecfm='ZON10M_TEB'
282  ycomment='X_Y_'//yrecfm//' (M/S)'
283  CALL write_surf(hselect,hprogram,yrecfm,d%XZON10M(:),iresp,hcomment=ycomment)
284  !
285  yrecfm='MER10M_TEB'
286  ycomment='X_Y_'//yrecfm//' (M/S)'
287  CALL write_surf(hselect,hprogram,yrecfm,d%XMER10M(:),iresp,hcomment=ycomment)
288  !
289  yrecfm='W10M_TEB'
290  ycomment='X_Y_'//yrecfm//' (M/S)'
291  CALL write_surf(hselect,hprogram,yrecfm,d%XWIND10M(:),iresp,hcomment=ycomment)
292  !
293  yrecfm='W10MMAX_TEB'
294  ycomment='X_Y_'//yrecfm//' (M/S)'
295  CALL write_surf(hselect,hprogram,yrecfm,d%XWIND10M_MAX(:),iresp,hcomment=ycomment)
296  IF(greset)d%XWIND10M_MAX(:)=0.0
297  !
298  yrecfm='SFCO2_TEB'
299  ycomment='X_Y_'//yrecfm//' (M.kgCO2.S-1.kgAIR-1)'
300  CALL write_surf(hselect,hprogram,yrecfm,d%XSFCO2(:),iresp,hcomment=ycomment)
301  !
302 END IF
303 !
304 IF (dut%LUTCI .AND. dgo%N2M >0) THEN
305  yrecfm='UTCI_IN'
306 !RJ: extended ascii should be avoided in I/O
307  ycomment='UTCI for person indoor'//' (°C)'
308  CALL write_surf(hselect,hprogram,yrecfm,dut%XUTCI_IN(:),iresp,hcomment=ycomment)
309  !
310  yrecfm='UTCI_OUTSUN'
311 !RJ: extended ascii should be avoided in I/O
312  ycomment='UTCI for person at sun'//' (°C)'
313  CALL write_surf(hselect,hprogram,yrecfm,dut%XUTCI_OUTSUN(:),iresp,hcomment=ycomment)
314  !
315  yrecfm='UTCI_OUTSHAD'
316 !RJ: extended ascii should be avoided in I/O
317  ycomment='UTCI for person in shade'//' (°C)'
318  CALL write_surf(hselect,hprogram,yrecfm,dut%XUTCI_OUTSHADE(:),iresp,hcomment=ycomment)
319  !
320  yrecfm='TRAD_SUN'
321  ycomment='Mean radiant temperature seen by person at sun'//' (K)'
322  CALL write_surf(hselect,hprogram,yrecfm,dut%XTRAD_SUN(:),iresp,hcomment=ycomment)
323  !
324  yrecfm='TRAD_SHADE'
325  ycomment='Mean radiant temperature seen by person in shade'//' (K)'
326  CALL write_surf(hselect,hprogram,yrecfm,dut%XTRAD_SHADE(:),iresp,hcomment=ycomment)
327  !
328  DO jstress=1,nutci_stress
329  yrecfm='UTCIC_IN_'//cutci_stress_names(jstress)
330  ycomment='Cumulated time spent in '//cutci_stress_names(jstress)//' stress range for person indoor'//' (s)'
331  CALL write_surf(hselect,hprogram,yrecfm,dut%XUTCIC_IN(:,jstress),iresp,hcomment=ycomment)
332  END DO
333  !
334  DO jstress=1,nutci_stress
335  yrecfm='UTCIC_SU_'//cutci_stress_names(jstress)
336  ycomment='Cumulated time spent in '//cutci_stress_names(jstress)//' stress range for person at sun'//' (s)'
337  CALL write_surf(hselect,hprogram,yrecfm,dut%XUTCIC_OUTSUN(:,jstress),iresp,hcomment=ycomment)
338  END DO
339  !
340  DO jstress=1,nutci_stress
341  yrecfm='UTCIC_SH_'//cutci_stress_names(jstress)
342  ycomment='Cumulated time spent in '//cutci_stress_names(jstress)//' stress range for person in shade'//' (s)'
343  CALL write_surf(hselect,hprogram,yrecfm,dut%XUTCIC_OUTSHADE(:,jstress),iresp,hcomment=ycomment)
344  END DO
345 END IF
346 !
347 !
348 !* 6. chemical diagnostics:
349 ! --------------------
350 !
351 IF (cht%SVT%NBEQ>0 .AND. cht%CCH_DRY_DEP=="WES89 ") THEN
352  DO jsv = 1,SIZE(cht%CCH_NAMES,1)
353  yrecfm='DVTN'//trim(cht%CCH_NAMES(jsv))
354  WRITE(ycomment,'(A13,I3.3)')'(m/s) DV_TWN_',jsv
355  CALL write_surf(hselect,hprogram,yrecfm,cht%XDEP(:,jsv),iresp,hcomment=ycomment)
356  END DO
357 ENDIF
358 !-------------------------------------------------------------------------------
359 !
360 ! End of IO
361 !
362  CALL end_io_surf_n(hprogram)
363 IF (lhook) CALL dr_hook('WRITE_DIAG_SEB_TEB_N',1,zhook_handle)
364 !
365 !
366 END SUBROUTINE write_diag_seb_teb_n
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
integer, parameter nutci_stress
Definition: modd_utci.F90:38
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lallow_add_dim
Definition: modd_xios.F90:49
subroutine write_diag_seb_teb_n(DTCO, HSELECT, U, CHT, DGO, D, DU
character(len=30) yswband_dim_name
Definition: modd_xios.F90:69
subroutine end_io_surf_n(HPROGRAM)
Definition: end_io_surfn.F90:7
character(len=3), dimension(nutci_stress), parameter cutci_stress_names
Definition: modd_utci.F90:42
logical lhook
Definition: yomhook.F90:15
subroutine init_io_surf_n(DTCO, U, HPROGRAM, HMASK, HSCHEME, HACTION