SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
write_diag_seb_flaken.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_flake_n (DTCO, DGU, U, CHF, DGF, &
7  hprogram)
8 ! #################################
9 !
10 !!**** *WRITE_DIAG_SEB_FLAKE_n* - writes FLAKE diagnostics
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!
16 !!** METHOD
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 : sea flux parameterization.
31 !! P.LeMoigne 04/2013 : Add accumulated diagnostics
32 !! Modified 04/2013, P. Le Moigne: FLake chemistry
33 !! S. Belamari 06/2014 : Introduce NBLOCK to avoid errors due to NBLOCK=0
34 !! when coupled with ARPEGE/ALADIN/AROME
35 !! B. Decharme 02/2016 : NBLOCK instead of LCOUNTW for compilation in AAA
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 !
44 USE modd_surf_atm_n, ONLY : surf_atm_t
45 USE modd_ch_flake_n, ONLY : ch_flake_t
47 !
48 #ifdef SFX_ARO
49 USE modd_io_surf_aro, ONLY : nblock
50 #endif
51 !
52 USE modd_surf_par, ONLY : xundef
53 !
54 !
55 !
56 !
57 USE modi_init_io_surf_n
59 USE modi_end_io_surf_n
60 !
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 !
72 TYPE(data_cover_t), INTENT(INOUT) :: dtco
73 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
74 TYPE(surf_atm_t), INTENT(INOUT) :: u
75 TYPE(ch_flake_t), INTENT(INOUT) :: chf
76 TYPE(diag_flake_t), INTENT(INOUT) :: dgf
77 !
78  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
79 !
80 !* 0.2 Declarations of local variables
81 ! -------------------------------
82 !
83 INTEGER :: iresp ! IRESP : return-code if a problem appears
84  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
85  CHARACTER(LEN=100):: ycomment ! Comment string
86  CHARACTER(LEN=2) :: ynum
87 !
88 LOGICAL :: greset
89 INTEGER :: jsv, jsw
90 REAL(KIND=JPRB) :: zhook_handle
91 !-------------------------------------------------------------------------------
92 !
93 ! Initialisation for IO
94 !
95 IF (lhook) CALL dr_hook('WRITE_DIAG_SEB_FLAKE_N',0,zhook_handle)
96 !
97 greset=.true.
98 #ifdef SFX_ARO
99 greset=(nblock>0)
100 #endif
101 !
102  CALL init_io_surf_n(dtco, dgu, u, &
103  hprogram,'WATER ','FLAKE ','WRITE')
104 !
105 !
106 !* 2. Richardson number :
107 ! -----------------
108 !
109 IF (dgf%N2M>=1) THEN
110 
111 yrecfm='RI_WAT'
112 ycomment='Bulk-Richardson number for water'
113 !
114  CALL write_surf(dgu, u, &
115  hprogram,yrecfm,dgf%XRI(:),iresp,hcomment=ycomment)
116 !
117 END IF
118 !
119 !* 3. Energy fluxes :
120 ! -------------
121 !
122 IF (dgf%LSURF_BUDGET) THEN
123 
124 yrecfm='RN_WAT'
125 ycomment='net radiation for water'//' (W/m2)'
126 !
127  CALL write_surf(dgu, u, &
128  hprogram,yrecfm,dgf%XRN(:),iresp,hcomment=ycomment)
129 !
130 yrecfm='H_WAT'
131 ycomment='sensible heat flux for water'//' (W/m2)'
132 !
133  CALL write_surf(dgu, u, &
134  hprogram,yrecfm,dgf%XH(:),iresp,hcomment=ycomment)
135 !
136 yrecfm='LE_WAT'
137 ycomment='total latent heat flux for water'//' (W/m2)'
138 !
139  CALL write_surf(dgu, u, &
140  hprogram,yrecfm,dgf%XLE(:),iresp,hcomment=ycomment)
141 !
142 yrecfm='LEI_WAT'
143 ycomment='sublimation latent heat flux for water-ice'//' (W/m2)'
144 !
145  CALL write_surf(dgu, u, &
146  hprogram,yrecfm,dgf%XLEI(:),iresp,hcomment=ycomment)
147 !
148 yrecfm='GFLUX_WAT'
149 ycomment='conduction flux for water'//' (W/m2)'
150 !
151  CALL write_surf(dgu, u, &
152  hprogram,yrecfm,dgf%XGFLUX(:),iresp,hcomment=ycomment)
153 !
154 yrecfm='EVAP_WAT'
155 ycomment='X_Y_'//yrecfm//' (kg/m2/s)'
156 !
157  CALL write_surf(dgu, u, &
158  hprogram,yrecfm,dgf%XEVAP(:),iresp,hcomment=ycomment)
159 !
160 yrecfm='SUBL_WAT'
161 ycomment='X_Y_'//yrecfm//' (kg/m2/s)'
162 !
163  CALL write_surf(dgu, u, &
164  hprogram,yrecfm,dgf%XSUBL(:),iresp,hcomment=ycomment)
165 !
166 IF (dgf%LRAD_BUDGET) THEN
167 !
168  yrecfm='SWD_WAT'
169  ycomment='short wave downward radiation for water'//' (W/m2)'
170  !
171  CALL write_surf(dgu, u, &
172  hprogram,yrecfm,dgf%XSWD(:),iresp,hcomment=ycomment)
173  !
174  yrecfm='SWU_WAT'
175  ycomment='short wave upward radiation for water'//' (W/m2)'
176  !
177  CALL write_surf(dgu, u, &
178  hprogram,yrecfm,dgf%XSWU(:),iresp,hcomment=ycomment)
179  !
180  yrecfm='LWD_WAT'
181  ycomment='downward long wave radiation'//' (W/m2)'
182  !
183  CALL write_surf(dgu, u, &
184  hprogram,yrecfm,dgf%XLWD(:),iresp,hcomment=ycomment)
185  !
186  yrecfm='LWU_WAT'
187  ycomment='upward long wave radiation'//' (W/m2)'
188  !
189  CALL write_surf(dgu, u, &
190  hprogram,yrecfm,dgf%XLWU(:),iresp,hcomment=ycomment)
191  !
192  DO jsw=1, SIZE(dgf%XSWBD,2)
193  ynum=achar(48+jsw)
194  !
195  yrecfm='SWD_WAT_'//ynum
196  ycomment='downward short wave radiation by spectral band '//' (W/m2)'
197  !
198  CALL write_surf(dgu, u, &
199  hprogram,yrecfm,dgf%XSWBD(:,jsw),iresp,hcomment=ycomment)
200  !
201  yrecfm='SWU_WAT_'//ynum
202  ycomment='upward short wave radiation by spectral band'//' (W/m2)'
203  !
204  CALL write_surf(dgu, u, &
205  hprogram,yrecfm,dgf%XSWBU(:,jsw),iresp,hcomment=ycomment)
206  !
207  ENDDO
208 !
209 ENDIF
210 !
211 yrecfm='FMU_WAT'
212 ycomment='u-component of momentum flux for water'//' (kg/ms2)'
213 !
214  CALL write_surf(dgu, u, &
215  hprogram,yrecfm,dgf%XFMU(:),iresp,hcomment=ycomment)
216 yrecfm='FMV_WAT'
217 ycomment='v-component of momentum flux for water'//' (kg/ms2)'
218 !
219  CALL write_surf(dgu, u, &
220  hprogram,yrecfm,dgf%XFMV(:),iresp,hcomment=ycomment)
221 !
222 END IF
223 !
224 IF (dgf%LSURF_BUDGET.OR.dgf%LSURF_BUDGETC) THEN
225 !
226  yrecfm='TALB_WAT'
227  ycomment='total albedo over tile water (-)'
228  CALL write_surf(dgu, u, &
229  hprogram,yrecfm,dgf%XALBT(:),iresp,hcomment=ycomment)
230 !
231  yrecfm='WSN_WAT'
232  ycomment='snow water equivalent over tile water (-)'
233  CALL write_surf(dgu, u, &
234  hprogram,yrecfm,dgf%XSWE(:),iresp,hcomment=ycomment)
235 !
236 ENDIF
237 !
238 IF (dgf%LSURF_BUDGETC) THEN
239 !
240 yrecfm='RNC_WAT'
241 ycomment='X_Y_'//yrecfm//' (J/m2)'
242 !
243  CALL write_surf(dgu, u, &
244  hprogram,yrecfm,dgf%XRNC(:),iresp,hcomment=ycomment)
245 !
246 yrecfm='HC_WAT'
247 ycomment='X_Y_'//yrecfm//' (J/m2)'
248 !
249  CALL write_surf(dgu, u, &
250  hprogram,yrecfm,dgf%XHC(:),iresp,hcomment=ycomment)
251 !
252 yrecfm='LEC_WAT'
253 ycomment='X_Y_'//yrecfm//' (J/m2)'
254 !
255  CALL write_surf(dgu, u, &
256  hprogram,yrecfm,dgf%XLEC(:),iresp,hcomment=ycomment)
257 !
258 yrecfm='LEIC_WAT'
259 ycomment='X_Y_'//yrecfm//' (J/m2)'
260 !
261  CALL write_surf(dgu, u, &
262  hprogram,yrecfm,dgf%XLEIC(:),iresp,hcomment=ycomment)
263 !
264 yrecfm='GFLUXC_WAT'
265 ycomment='X_Y_'//yrecfm//' (J/m2)'
266 !
267  CALL write_surf(dgu, u, &
268  hprogram,yrecfm,dgf%XGFLUXC(:),iresp,hcomment=ycomment)
269 !
270 yrecfm='EVAPC_WAT'
271 ycomment='X_Y_'//yrecfm//' (kg/m2)'
272 !
273  CALL write_surf(dgu, u, &
274  hprogram,yrecfm,dgf%XEVAPC(:),iresp,hcomment=ycomment)
275 !
276 yrecfm='SUBLC_WAT'
277 ycomment='X_Y_'//yrecfm//' (kg/m2)'
278 !
279  CALL write_surf(dgu, u, &
280  hprogram,yrecfm,dgf%XSUBLC(:),iresp,hcomment=ycomment)
281 !
282 IF (dgf%LRAD_BUDGET .OR. (dgf%LSURF_BUDGETC .AND. .NOT.dgu%LRESET_BUDGETC)) THEN
283 !
284  yrecfm='SWDC_WAT'
285  ycomment='X_Y_'//yrecfm//' (J/m2)'
286  !
287  CALL write_surf(dgu, u, &
288  hprogram,yrecfm,dgf%XSWDC(:),iresp,hcomment=ycomment)
289  !
290  yrecfm='SWUC_WAT'
291  ycomment='X_Y_'//yrecfm//' (J/m2)'
292  !
293  CALL write_surf(dgu, u, &
294  hprogram,yrecfm,dgf%XSWUC(:),iresp,hcomment=ycomment)
295  !
296  yrecfm='LWDC_WAT'
297  ycomment='X_Y_'//yrecfm//' (J/m2)'
298  !
299  CALL write_surf(dgu, u, &
300  hprogram,yrecfm,dgf%XLWDC(:),iresp,hcomment=ycomment)
301  !
302  yrecfm='LWUC_WAT'
303  ycomment='X_Y_'//yrecfm//' (J/m2)'
304  !
305  CALL write_surf(dgu, u, &
306  hprogram,yrecfm,dgf%XLWUC(:),iresp,hcomment=ycomment)
307 !
308 ENDIF
309 !
310 yrecfm='FMUC_WAT'
311 ycomment='X_Y_'//yrecfm//' (kg/ms)'
312 !
313  CALL write_surf(dgu, u, &
314  hprogram,yrecfm,dgf%XFMUC(:),iresp,hcomment=ycomment)
315 !
316 yrecfm='FMVC_WAT'
317 ycomment='X_Y_'//yrecfm//' (kg/ms)'
318 !
319  CALL write_surf(dgu, u, &
320  hprogram,yrecfm,dgf%XFMVC(:),iresp,hcomment=ycomment)
321 !
322 END IF
323 !
324 !
325 !* 4. Transfer coefficients
326 ! ---------------------
327 !
328 IF (dgf%LCOEF) THEN
329 
330 yrecfm='CD_WAT'
331 ycomment='drag coefficient for wind over water (W/s2)'
332 !
333  CALL write_surf(dgu, u, &
334  hprogram,yrecfm,dgf%XCD(:),iresp,hcomment=ycomment)
335 !
336 yrecfm='CH_WAT'
337 ycomment='drag coefficient for heat (W/s)'
338 !
339  CALL write_surf(dgu, u, &
340  hprogram,yrecfm,dgf%XCH(:),iresp,hcomment=ycomment)
341 !
342 yrecfm='CE_WAT'
343 ycomment='drag coefficient for vapor (W/s/K)'
344 !
345  CALL write_surf(dgu, u, &
346  hprogram,yrecfm,dgf%XCE(:),iresp,hcomment=ycomment)
347 !
348 yrecfm='Z0_WAT'
349 ycomment='roughness length over water (m)'
350 
351  CALL write_surf(dgu, u, &
352  hprogram,yrecfm,dgf%XZ0(:),iresp,hcomment=ycomment)
353 !
354 yrecfm='Z0H_WAT'
355 ycomment='thermal roughness length over water (m)'
356 !
357  CALL write_surf(dgu, u, &
358  hprogram,yrecfm,dgf%XZ0H(:),iresp,hcomment=ycomment)
359 !
360 END IF
361 !
362 !
363 !* 5. Surface humidity
364 ! ----------------
365 !
366 IF (dgf%LSURF_VARS) THEN
367 
368 yrecfm='QS_WAT'
369 ycomment='specific humidity over water'//' (KG/KG)'
370 !
371  CALL write_surf(dgu, u, &
372  hprogram,yrecfm,dgf%XQS(:),iresp,hcomment=ycomment)
373 !
374 ENDIF
375 !
376 
377 !
378 !* 6. parameters at 2 and 10 meters :
379 ! -----------------------------
380 !
381 IF (dgf%N2M>=1) THEN
382 !
383 yrecfm='T2M_WAT'
384 ycomment='2 meters temperature'//' (K)'
385 !
386  CALL write_surf(dgu, u, &
387  hprogram,yrecfm,dgf%XT2M(:),iresp,hcomment=ycomment)
388 !
389 yrecfm='T2MMIN_WAT'
390 ycomment='X_Y_'//yrecfm//' (K)'
391 !
392  CALL write_surf(dgu, u, &
393  hprogram,yrecfm,dgf%XT2M_MIN(:),iresp,hcomment=ycomment)
394 IF(greset)dgf%XT2M_MIN(:)=xundef
395 !
396 yrecfm='T2MMAX_WAT'
397 ycomment='X_Y_'//yrecfm//' (K)'
398 !
399  CALL write_surf(dgu, u, &
400  hprogram,yrecfm,dgf%XT2M_MAX(:),iresp,hcomment=ycomment)
401 IF(greset)dgf%XT2M_MAX(:)=0.0
402 !
403 yrecfm='Q2M_WAT'
404 ycomment='2 meters specific humidity'//' (KG/KG)'
405 !
406  CALL write_surf(dgu, u, &
407  hprogram,yrecfm,dgf%XQ2M(:),iresp,hcomment=ycomment)
408 !
409 yrecfm='HU2M_WAT'
410 ycomment='2 meters relative humidity'//' (KG/KG)'
411 !
412  CALL write_surf(dgu, u, &
413  hprogram,yrecfm,dgf%XHU2M(:),iresp,hcomment=ycomment)
414 !
415 yrecfm='HU2MMIN_WAT'
416 ycomment='X_Y_'//yrecfm//' (-)'
417 !
418  CALL write_surf(dgu, u, &
419  hprogram,yrecfm,dgf%XHU2M_MIN(:),iresp,hcomment=ycomment)
420 IF(greset)dgf%XHU2M_MIN(:)=xundef
421 !
422 yrecfm='HU2MMAX_WAT'
423 ycomment='X_Y_'//yrecfm//' (-)'
424 !
425  CALL write_surf(dgu, u, &
426  hprogram,yrecfm,dgf%XHU2M_MAX(:),iresp,hcomment=ycomment)
427 IF(greset)dgf%XHU2M_MAX(:)=-xundef
428 !
429 yrecfm='ZON10M_WAT'
430 ycomment='10 meters zonal wind'//' (M/S)'
431 !
432  CALL write_surf(dgu, u, &
433  hprogram,yrecfm,dgf%XZON10M(:),iresp,hcomment=ycomment)
434 !
435 yrecfm='MER10M_WAT'
436 ycomment='10 meters meridian wind'//' (M/S)'
437 !
438  CALL write_surf(dgu, u, &
439  hprogram,yrecfm,dgf%XMER10M(:),iresp,hcomment=ycomment)
440 !
441 yrecfm='W10M_WAT'
442 ycomment='X_Y_'//yrecfm//' (M/S)'
443 !
444  CALL write_surf(dgu, u, &
445  hprogram,yrecfm,dgf%XWIND10M(:),iresp,hcomment=ycomment)
446 !
447 yrecfm='W10MMAX_WAT'
448 ycomment='X_Y_'//yrecfm//' (M/S)'
449 !
450  CALL write_surf(dgu, u, &
451  hprogram,yrecfm,dgf%XWIND10M_MAX(:),iresp,hcomment=ycomment)
452 IF(greset)dgf%XWIND10M_MAX(:)=0.0
453 !
454 END IF
455 !
456 !
457 !* 7. chemical diagnostics:
458 ! --------------------
459 !
460 IF (chf%SVF%NBEQ>0 .AND. chf%CCH_DRY_DEP=="WES89 ") THEN
461  DO jsv = 1,SIZE(chf%CCH_NAMES,1)
462  yrecfm='DV_WAT_'//trim(chf%CCH_NAMES(jsv))
463  WRITE(ycomment,'(A13,I3.3)')'(m/s) DV_WAT_',jsv
464  CALL write_surf(dgu, u, &
465  hprogram,yrecfm,chf%XDEP(:,jsv),iresp,hcomment=ycomment)
466  END DO
467 ENDIF
468 !
469 !
470 !* 8. prognostic variable diagnostics:
471 ! --------------------------------
472 !
473 IF(dgu%LPROVAR_TO_DIAG)THEN
474 !
475  yrecfm='TS_WATER'
476  ycomment='TS_WATER (K)'
477  CALL write_surf(dgu, u, &
478  hprogram,yrecfm,dgf%XDIAG_TS(:),iresp,hcomment=ycomment)
479 !
480 ENDIF
481 !
482 !-------------------------------------------------------------------------------
483 !
484 ! End of IO
485 !
486  CALL end_io_surf_n(hprogram)
487 IF (lhook) CALL dr_hook('WRITE_DIAG_SEB_FLAKE_N',1,zhook_handle)
488 !
489 !
490 END SUBROUTINE write_diag_seb_flake_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_flake_n(DTCO, DGU, U, CHF, DGF, HPROGRAM)