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