SURFEX v8.1
General documentation of Surfex
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, DUO, U, CHF, DFO, D, DC, HPROGRAM)
7 ! #################################
8 !
9 !!**** *WRITE_DIAG_SEB_FLAKE_n* - writes FLAKE diagnostics
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! V. Masson *Meteo France*
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2004
29 !! Modified 01/2006 : sea flux parameterization.
30 !! P.LeMoigne 04/2013 : Add accumulated diagnostics
31 !! Modified 04/2013, P. Le Moigne: FLake chemistry
32 !! S. Belamari 06/2014 : Introduce NBLOCK to avoid errors due to NBLOCK=0
33 !! when coupled with ARPEGE/ALADIN/AROME
34 !! B. Decharme 02/2016 : NBLOCK instead of LCOUNTW for compilation in AAA
35 !-------------------------------------------------------------------------------
36 !
37 !* 0. DECLARATIONS
38 ! ------------
39 !
40 !
43 USE modd_surf_atm_n, ONLY : surf_atm_t
44 USE modd_ch_flake_n, ONLY : ch_flake_t
45 !
47 !
48 USE modd_surf_par, ONLY : xundef
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 !
63 USE yomhook ,ONLY : lhook, dr_hook
64 USE parkind1 ,ONLY : jprb
65 !
66 IMPLICIT NONE
67 !
68 !* 0.1 Declarations of arguments
69 ! -------------------------
70 !
71 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
72 TYPE(diag_options_t), INTENT(INOUT) :: DUO
73 TYPE(surf_atm_t), INTENT(INOUT) :: U
74 TYPE(ch_flake_t), INTENT(INOUT) :: CHF
75 TYPE(diag_options_t), INTENT(INOUT) :: DFO
76 TYPE(diag_t), INTENT(INOUT) :: D
77 TYPE(diag_t), INTENT(INOUT) :: DC
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 REAL(KIND=JPRB) :: ZHOOK_HANDLE
92 !-------------------------------------------------------------------------------
93 !
94 ! Initialisation for IO
95 !
96 IF (lhook) CALL dr_hook('WRITE_DIAG_SEB_FLAKE_N',0,zhook_handle)
97 !
98 greset=.true.
99 #ifdef SFX_ARO
100 greset=(nblock>0)
101 #endif
102 #ifdef SFX_OL
103 IF (ldef) greset = .false.
104 #endif
105 !
106  CALL init_io_surf_n(dtco, u, hprogram,'WATER ','FLAKE ','WRITE','FLAKE_DIAGNOSTICS.OUT.nc')
107 !
108 !
109 !* 2. Richardson number :
110 ! -----------------
111 !
112 IF (dfo%N2M>=1) THEN
113 
114  yrecfm='RI_WAT'
115  ycomment='Bulk-Richardson number for water'
116  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XRI(:),iresp,hcomment=ycomment)
117 !
118 END IF
119 !
120 !* 3. Energy fluxes :
121 ! -------------
122 !
123 IF (dfo%LSURF_BUDGET) THEN
124 
125  yrecfm='RN_WAT'
126  ycomment='net radiation for water'//' (W/m2)'
127  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XRN(:),iresp,hcomment=ycomment)
128  !
129  yrecfm='H_WAT'
130  ycomment='sensible heat flux for water'//' (W/m2)'
131  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XH(:),iresp,hcomment=ycomment)
132  !
133  yrecfm='LE_WAT'
134  ycomment='total latent heat flux for water'//' (W/m2)'
135  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XLE(:),iresp,hcomment=ycomment)
136  !
137  yrecfm='LEI_WAT'
138  ycomment='sublimation latent heat flux for water-ice'//' (W/m2)'
139  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XLEI(:),iresp,hcomment=ycomment)
140  !
141  yrecfm='GFLUX_WAT'
142  ycomment='conduction flux for water'//' (W/m2)'
143  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XGFLUX(:),iresp,hcomment=ycomment)
144  !
145  yrecfm='EVAP_WAT'
146  ycomment='X_Y_'//yrecfm//' (kg/m2/s)'
147  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XEVAP(:),iresp,hcomment=ycomment)
148  !
149  yrecfm='SUBL_WAT'
150  ycomment='X_Y_'//yrecfm//' (kg/m2/s)'
151  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XSUBL(:),iresp,hcomment=ycomment)
152  !
153  IF (dfo%LRAD_BUDGET) THEN
154  !
155  yrecfm='SWD_WAT'
156  ycomment='short wave downward radiation for water'//' (W/m2)'
157  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XSWD(:),iresp,hcomment=ycomment)
158  !
159  yrecfm='SWU_WAT'
160  ycomment='short wave upward radiation for water'//' (W/m2)'
161  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XSWU(:),iresp,hcomment=ycomment)
162  !
163  yrecfm='LWD_WAT'
164  ycomment='downward long wave radiation'//' (W/m2)'
165  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XLWD(:),iresp,hcomment=ycomment)
166  !
167  yrecfm='LWU_WAT'
168  ycomment='upward long wave radiation'//' (W/m2)'
169  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XLWU(:),iresp,hcomment=ycomment)
170  !
171  IF (lallow_add_dim) THEN
172  !
173  yrecfm='SWD_WAT'
174  ycomment='X_Y_'//yrecfm//' (W/m2)'
175  CALL write_surf(duo%CSELECT,&
176  hprogram,yrecfm,d%XSWBD(:,:),iresp,hcomment=ycomment, hnam_dim=yswband_dim_name)
177  !
178  yrecfm='SWU_WAT'
179  ycomment='X_Y_'//yrecfm//' (W/m2)'
180  CALL write_surf(duo%CSELECT,&
181  hprogram,yrecfm,d%XSWBD(:,:),iresp,hcomment=ycomment, hnam_dim=yswband_dim_name)
182  !
183  ELSE
184  !
185  DO jsw=1, SIZE(d%XSWBD,2)
186  ynum=achar(48+jsw)
187  !
188  yrecfm='SWD_WAT_'//ynum
189  ycomment='downward short wave radiation by spectral band '//' (W/m2)'
190  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XSWBD(:,jsw),iresp,hcomment=ycomment)
191  !
192  yrecfm='SWU_WAT_'//ynum
193  ycomment='upward short wave radiation by spectral band'//' (W/m2)'
194  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XSWBU(:,jsw),iresp,hcomment=ycomment)
195  !
196  ENDDO
197  !
198  ENDIF
199  !
200  ENDIF
201  !
202  yrecfm='FMU_WAT'
203  ycomment='u-component of momentum flux for water'//' (kg/ms2)'
204  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XFMU(:),iresp,hcomment=ycomment)
205  !
206  yrecfm='FMV_WAT'
207  ycomment='v-component of momentum flux for water'//' (kg/ms2)'
208  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XFMV(:),iresp,hcomment=ycomment)
209  !
210 END IF
211 !
212 IF (dfo%LSURF_BUDGET.OR.dfo%LSURF_BUDGETC) THEN
213 !
214  yrecfm='TALB_WAT'
215  ycomment='total albedo over tile water (-)'
216  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XALBT(:),iresp,hcomment=ycomment)
217 !
218  yrecfm='WSN_WAT'
219  ycomment='snow water equivalent over tile water (-)'
220  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XSWE(:),iresp,hcomment=ycomment)
221 !
222 ENDIF
223 !
224 !
225 !* 4. Transfer coefficients
226 ! ---------------------
227 !
228 IF (dfo%LCOEF) THEN
229 
230  yrecfm='CD_WAT'
231  ycomment='drag coefficient for wind over water (W/s2)'
232  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XCD(:),iresp,hcomment=ycomment)
233  !
234  yrecfm='CH_WAT'
235  ycomment='drag coefficient for heat (W/s)'
236  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XCH(:),iresp,hcomment=ycomment)
237  !
238  yrecfm='CE_WAT'
239  ycomment='drag coefficient for vapor (W/s/K)'
240  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XCE(:),iresp,hcomment=ycomment)
241  !
242  yrecfm='Z0_WAT'
243  ycomment='roughness length over water (m)'
244  CALL write_surf(duo%CSELECT, hprogram,yrecfm,d%XZ0(:),iresp,hcomment=ycomment)
245  !
246  yrecfm='Z0H_WAT'
247  ycomment='thermal roughness length over water (m)'
248  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XZ0H(:),iresp,hcomment=ycomment)
249  !
250 END IF
251 !
252 !
253 !* 5. Surface humidity
254 ! ----------------
255 !
256 IF (dfo%LSURF_VARS) THEN
257 
258  yrecfm='QS_WAT'
259  ycomment='specific humidity over water'//' (KG/KG)'
260  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XQS(:),iresp,hcomment=ycomment)
261  !
262 ENDIF
263 !
264 
265 !
266 !* 6. parameters at 2 and 10 meters :
267 ! -----------------------------
268 !
269 IF (dfo%N2M>=1) THEN
270  !
271  yrecfm='T2M_WAT'
272  ycomment='2 meters temperature'//' (K)'
273  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XT2M(:),iresp,hcomment=ycomment)
274  !
275  yrecfm='T2MMIN_WAT'
276  ycomment='X_Y_'//yrecfm//' (K)'
277  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XT2M_MIN(:),iresp,hcomment=ycomment)
278  IF(greset)d%XT2M_MIN(:)=xundef
279  !
280  yrecfm='T2MMAX_WAT'
281  ycomment='X_Y_'//yrecfm//' (K)'
282  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XT2M_MAX(:),iresp,hcomment=ycomment)
283  IF(greset)d%XT2M_MAX(:)=0.0
284  !
285  yrecfm='Q2M_WAT'
286  ycomment='2 meters specific humidity'//' (KG/KG)'
287  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XQ2M(:),iresp,hcomment=ycomment)
288  !
289  yrecfm='HU2M_WAT'
290  ycomment='2 meters relative humidity'//' (KG/KG)'
291  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XHU2M(:),iresp,hcomment=ycomment)
292  !
293  yrecfm='HU2MMIN_WAT'
294  ycomment='X_Y_'//yrecfm//' (-)'
295  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XHU2M_MIN(:),iresp,hcomment=ycomment)
296  IF(greset)d%XHU2M_MIN(:)=xundef
297  !
298  yrecfm='HU2MMAX_WAT'
299  ycomment='X_Y_'//yrecfm//' (-)'
300  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XHU2M_MAX(:),iresp,hcomment=ycomment)
301  IF(greset)d%XHU2M_MAX(:)=-xundef
302  !
303  yrecfm='ZON10M_WAT'
304  ycomment='10 meters zonal wind'//' (M/S)'
305  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XZON10M(:),iresp,hcomment=ycomment)
306  !
307  yrecfm='MER10M_WAT'
308  ycomment='10 meters meridian wind'//' (M/S)'
309  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XMER10M(:),iresp,hcomment=ycomment)
310  !
311  yrecfm='W10M_WAT'
312  ycomment='X_Y_'//yrecfm//' (M/S)'
313  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XWIND10M(:),iresp,hcomment=ycomment)
314  !
315  yrecfm='W10MMAX_WAT'
316  ycomment='X_Y_'//yrecfm//' (M/S)'
317  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XWIND10M_MAX(:),iresp,hcomment=ycomment)
318  IF(greset)d%XWIND10M_MAX(:)=0.0
319  !
320 END IF
321 !
322 !
323 !* 7. chemical diagnostics:
324 ! --------------------
325 !
326 IF (chf%SVF%NBEQ>0 .AND. chf%CCH_DRY_DEP=="WES89 ") THEN
327  DO jsv = 1,SIZE(chf%CCH_NAMES,1)
328  yrecfm='DVWT'//trim(chf%CCH_NAMES(jsv))
329  WRITE(ycomment,'(A13,I3.3)')'(m/s) DV_WAT_',jsv
330  CALL write_surf(duo%CSELECT,hprogram,yrecfm,chf%XDEP(:,jsv),iresp,hcomment=ycomment)
331  END DO
332 ENDIF
333 !
334 !
335 !* 8. prognostic variable diagnostics:
336 ! --------------------------------
337 !
338 IF(duo%LPROVAR_TO_DIAG)THEN
339 !
340  yrecfm='TS_WAT'
341  ycomment='TS_WATER (K)'
342  CALL write_surf(duo%CSELECT,hprogram,yrecfm,d%XTS(:),iresp,hcomment=ycomment)
343 !
344 ENDIF
345 !
346 IF (dfo%LSURF_BUDGETC) THEN
347  !
348  CALL end_io_surf_n(hprogram)
349  CALL init_io_surf_n(dtco, u, hprogram,'WATER ','FLAKE ','WRITE','FLAKE_DIAGNOSTICS.OUT.nc')
350  !
351  yrecfm='RNC_WAT'
352  ycomment='X_Y_'//yrecfm//' (J/m2)'
353  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XRN(:),iresp,hcomment=ycomment)
354  !
355  yrecfm='HC_WAT'
356  ycomment='X_Y_'//yrecfm//' (J/m2)'
357  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XH(:),iresp,hcomment=ycomment)
358  !
359  yrecfm='LEC_WAT'
360  ycomment='X_Y_'//yrecfm//' (J/m2)'
361  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XLE(:),iresp,hcomment=ycomment)
362  !
363  yrecfm='LEIC_WAT'
364  ycomment='X_Y_'//yrecfm//' (J/m2)'
365  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XLEI(:),iresp,hcomment=ycomment)
366  !
367  yrecfm='GFLUXC_WAT'
368  ycomment='X_Y_'//yrecfm//' (J/m2)'
369  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XGFLUX(:),iresp,hcomment=ycomment)
370  !
371  yrecfm='EVAPC_WAT'
372  ycomment='X_Y_'//yrecfm//' (kg/m2)'
373  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XEVAP(:),iresp,hcomment=ycomment)
374  !
375  yrecfm='SUBLC_WAT'
376  ycomment='X_Y_'//yrecfm//' (kg/m2)'
377  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XSUBL(:),iresp,hcomment=ycomment)
378  !
379  IF (dfo%LRAD_BUDGET .OR. (dfo%LSURF_BUDGETC .AND. .NOT.duo%LRESET_BUDGETC)) THEN
380  !
381  yrecfm='SWDC_WAT'
382  ycomment='X_Y_'//yrecfm//' (J/m2)'
383  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XSWD(:),iresp,hcomment=ycomment)
384  !
385  yrecfm='SWUC_WAT'
386  ycomment='X_Y_'//yrecfm//' (J/m2)'
387  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XSWU(:),iresp,hcomment=ycomment)
388  !
389  yrecfm='LWDC_WAT'
390  ycomment='X_Y_'//yrecfm//' (J/m2)'
391  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XLWD(:),iresp,hcomment=ycomment)
392  !
393  yrecfm='LWUC_WAT'
394  ycomment='X_Y_'//yrecfm//' (J/m2)'
395  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XLWU(:),iresp,hcomment=ycomment)
396  !
397  ENDIF
398  !
399  yrecfm='FMUC_WAT'
400  ycomment='X_Y_'//yrecfm//' (kg/ms)'
401  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XFMU(:),iresp,hcomment=ycomment)
402  !
403  yrecfm='FMVC_WAT'
404  ycomment='X_Y_'//yrecfm//' (kg/ms)'
405  CALL write_surf(duo%CSELECT,hprogram,yrecfm,dc%XFMV(:),iresp,hcomment=ycomment)
406  !
407 END IF
408 !
409 !-------------------------------------------------------------------------------
410 !
411 ! End of IO
412 !
413  CALL end_io_surf_n(hprogram)
414 IF (lhook) CALL dr_hook('WRITE_DIAG_SEB_FLAKE_N',1,zhook_handle)
415 !
416 !
417 END SUBROUTINE write_diag_seb_flake_n
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lallow_add_dim
Definition: modd_xios.F90:49
subroutine write_diag_seb_flake_n(DTCO, DUO, U, CHF, DFO, D, DC,
character(len=30) yswband_dim_name
Definition: modd_xios.F90:69
subroutine end_io_surf_n(HPROGRAM)
Definition: end_io_surfn.F90:7
logical lhook
Definition: yomhook.F90:15
subroutine init_io_surf_n(DTCO, U, HPROGRAM, HMASK, HSCHEME, HACTION