SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
write_diag_seb_seaicen.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_seaice_n (DTCO, DGU, U, DGS, DGSI, S, &
7  hprogram)
8 ! #################################
9 !
10 !!**** *WRITE_DIAG_SEB_SEAICE_n* - write the seaice diagnostic fields
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !!
23 !! AUTHOR
24 !! ------
25 !! S.Senesi *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 01/2014
30 !-------------------------------------------------------------------------------
31 !
32 !* 0. DECLARATIONS
33 ! ------------
34 !
35 !
38 USE modd_surf_atm_n, ONLY : surf_atm_t
41 USE modd_seaflux_n, ONLY : seaflux_t
42 !
43 USE modd_sfx_oasis, ONLY : lcpl_seaice
44 !
45 !
46 !
47 !
48 USE modi_init_io_surf_n
50 USE modi_end_io_surf_n
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declarations of arguments
58 ! -------------------------
59 !
60 TYPE(data_cover_t), INTENT(INOUT) :: dtco
61 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
62 TYPE(surf_atm_t), INTENT(INOUT) :: u
63 TYPE(diag_seaflux_t), INTENT(INOUT) :: dgs
64 TYPE(diag_seaice_t), INTENT(INOUT) :: dgsi
65 TYPE(seaflux_t), INTENT(INOUT) :: s
66 !
67  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
68 !
69 !* 0.2 Declarations of local variables
70 ! -------------------------------
71 !
72 INTEGER :: iresp ! IRESP : return-code if a problem appears
73  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
74  CHARACTER(LEN=100):: ycomment ! Comment string
75  CHARACTER(LEN=2) :: ynum
76 INTEGER :: jsv, jsw
77 !
78 REAL(KIND=JPRB) :: zhook_handle
79 !
80 !-------------------------------------------------------------------------------
81 !
82 ! Initialisation for IO
83 !
84 IF (lhook) CALL dr_hook('WRITE_DIAG_SEB_SEAICE_N',0,zhook_handle)
85 !
86  CALL init_io_surf_n(dtco, dgu, u, &
87  hprogram,'SEA ','SEAFLX','WRITE')
88 !
89 IF(lcpl_seaice.OR.s%LHANDLE_SIC)THEN
90 !
91  ycomment='Sea-ice temperature (K)'
92  CALL write_surf(dgu, u, &
93  hprogram,'TSICE',s%XTICE(:),iresp,ycomment)
94 !
95  ycomment='Sea-ice albedo (-)'
96  CALL write_surf(dgu, u, &
97  hprogram,'IALB',s%XICE_ALB(:),iresp,ycomment)
98 !
99 ENDIF
100 !
101 IF (trim(s%CSEAICE_SCHEME) == 'GELATO') THEN
102  ycomment='Sea-ice thickness (m)'
103  CALL write_surf(dgu, u, &
104  hprogram,'SIT',dgsi%XSIT(:),iresp,ycomment)
105  !
106  ycomment='Sea-ice snow depth (m)'
107  CALL write_surf(dgu, u, &
108  hprogram,'SND',dgsi%XSND(:),iresp,ycomment)
109  !
110  ycomment='Sea mixed layer temp for Glt (K)'
111  CALL write_surf(dgu, u, &
112  hprogram,'SIMLT',dgsi%XMLT(:),iresp,ycomment)
113  !
114 ENDIF
115 !
116 !
117 !* 8.2. Richardson number :
118 ! -----------------
119 IF (dgs%N2M>=1) THEN
120  !
121  yrecfm='RI_SEAICE'
122  ycomment='X_Y_'//yrecfm
123  !
124  CALL write_surf(dgu, u, &
125  hprogram,yrecfm,dgs%XRI_ICE(:),iresp,hcomment=ycomment)
126  !
127 END IF
128 !
129 !* 8.3 Energy fluxes :
130 ! -------------
131 !
132 IF (dgs%LSURF_BUDGET) THEN
133 
134  yrecfm='RN_SEAICE'
135  ycomment='X_Y_'//yrecfm//' (W/m2)'
136  !
137  CALL write_surf(dgu, u, &
138  hprogram,yrecfm,dgs%XRN_ICE(:),iresp,hcomment=ycomment)
139  !
140  yrecfm='H_SEAICE'
141  ycomment='X_Y_'//yrecfm//' (W/m2)'
142  !
143  CALL write_surf(dgu, u, &
144  hprogram,yrecfm,dgs%XH_ICE(:),iresp,hcomment=ycomment)
145  !
146  yrecfm='LE_SEAICE'
147  ycomment='X_Y_'//yrecfm//' (W/m2)'
148  !
149  CALL write_surf(dgu, u, &
150  hprogram,yrecfm,dgs%XLE_ICE(:),iresp,hcomment=ycomment)
151  !
152  yrecfm='GFLX_SEAICE'
153  ycomment='X_Y_'//yrecfm//' (W/m2)'
154  !
155  CALL write_surf(dgu, u, &
156  hprogram,yrecfm,dgs%XGFLUX_ICE(:),iresp,hcomment=ycomment)
157  !
158  IF (dgs%LRAD_BUDGET) THEN
159  !
160  yrecfm='SWU_SEAICE'
161  ycomment='X_Y_'//yrecfm//' (W/m2)'
162  !
163  CALL write_surf(dgu, u, &
164  hprogram,yrecfm,dgs%XSWU_ICE(:),iresp,hcomment=ycomment)
165  !
166  yrecfm='LWU_SEAICE'
167  ycomment='X_Y_'//yrecfm//' (W/m2)'
168  !
169  CALL write_surf(dgu, u, &
170  hprogram,yrecfm,dgs%XLWU_ICE(:),iresp,hcomment=ycomment)
171  !
172  DO jsw=1, SIZE(dgs%XSWBU_ICE,2)
173  ynum=achar(48+jsw)
174  !
175  yrecfm='SWU_SEAICE_'//ynum
176  ycomment='X_Y_'//yrecfm//' (W/m2)'
177  !
178  CALL write_surf(dgu, u, &
179  hprogram,yrecfm,dgs%XSWBU_ICE(:,jsw),iresp,hcomment=ycomment)
180  !
181  ENDDO
182  !
183  ENDIF
184  !
185  yrecfm='FMU_SEAICE'
186  ycomment='X_Y_'//yrecfm//' (kg/ms2)'
187  !
188  CALL write_surf(dgu, u, &
189  hprogram,yrecfm,dgs%XFMU_ICE(:),iresp,hcomment=ycomment)
190  !
191  yrecfm='FMV_SEAICE'
192  ycomment='X_Y_'//yrecfm//' (kg/ms2)'
193  !
194  CALL write_surf(dgu, u, &
195  hprogram,yrecfm,dgs%XFMV_ICE(:),iresp,hcomment=ycomment)
196  !
197 END IF
198 !
199 IF (dgs%LSURF_BUDGETC) THEN
200  !
201  yrecfm='RNC_SEAICE'
202  ycomment='X_Y_'//yrecfm//' (J/m2)'
203  !
204  CALL write_surf(dgu, u, &
205  hprogram,yrecfm,dgs%XRNC_ICE(:),iresp,hcomment=ycomment)
206  !
207  yrecfm='HC_SEAICE'
208  ycomment='X_Y_'//yrecfm//' (J/m2)'
209  !
210  CALL write_surf(dgu, u, &
211  hprogram,yrecfm,dgs%XHC_ICE(:),iresp,hcomment=ycomment)
212  !
213  yrecfm='LEC_SEAICE'
214  ycomment='X_Y_'//yrecfm//' (J/m2)'
215  !
216  CALL write_surf(dgu, u, &
217  hprogram,yrecfm,dgs%XLEC_ICE(:),iresp,hcomment=ycomment)
218  !
219  yrecfm='GFLXC_SEAICE'
220  ycomment='X_Y_'//yrecfm//' (J/m2)'
221  !
222  CALL write_surf(dgu, u, &
223  hprogram,yrecfm,dgs%XGFLUXC_ICE(:),iresp,hcomment=ycomment)
224  IF (dgs%LRAD_BUDGET .OR. (dgs%LSURF_BUDGETC .AND. .NOT.dgu%LRESET_BUDGETC)) THEN
225  !
226  yrecfm='SWUC_SEAICE'
227  ycomment='X_Y_'//yrecfm//' (J/m2)'
228  !
229  CALL write_surf(dgu, u, &
230  hprogram,yrecfm,dgs%XSWUC_ICE(:),iresp,hcomment=ycomment)
231  !
232  yrecfm='LWUC_SEAICE'
233  ycomment='X_Y_'//yrecfm//' (J/m2)'
234  !
235  CALL write_surf(dgu, u, &
236  hprogram,yrecfm,dgs%XLWUC_ICE(:),iresp,hcomment=ycomment)
237  !
238  ENDIF
239  !
240  yrecfm='FMUC_SEAICE'
241  ycomment='X_Y_'//yrecfm//' (kg/ms)'
242  !
243  CALL write_surf(dgu, u, &
244  hprogram,yrecfm,dgs%XFMUC_ICE(:),iresp,hcomment=ycomment)
245  !
246  yrecfm='FMVC_SEAICE'
247  ycomment='X_Y_'//yrecfm//' (kg/ms)'
248  !
249  CALL write_surf(dgu, u, &
250  hprogram,yrecfm,dgs%XFMVC_ICE(:),iresp,hcomment=ycomment)
251  !
252 END IF
253 !
254 !* 8.4 transfer coefficients
255 ! ---------------------
256 !
257 IF (dgs%LCOEF) THEN
258  !
259  yrecfm='CD_SEAICE'
260  ycomment='X_Y_'//yrecfm//' (W/s2)'
261  !
262  CALL write_surf(dgu, u, &
263  hprogram,yrecfm,dgs%XCD_ICE(:),iresp,hcomment=ycomment)
264  !
265  yrecfm='CH_SEAICE'
266  ycomment='X_Y_'//yrecfm//' (W/s)'
267  !
268  CALL write_surf(dgu, u, &
269  hprogram,yrecfm,dgs%XCH_ICE(:),iresp,hcomment=ycomment)
270  !
271  yrecfm='Z0_SEAICE'
272  ycomment='X_Y_'//yrecfm//' (M)'
273  !
274  CALL write_surf(dgu, u, &
275  hprogram,yrecfm,dgs%XZ0_ICE(:),iresp,hcomment=ycomment)
276  !
277  yrecfm='Z0H_SEAICE'
278  ycomment='X_Y_'//yrecfm//' (M)'
279  !
280  CALL write_surf(dgu, u, &
281  hprogram,yrecfm,dgs%XZ0H_ICE(:),iresp,hcomment=ycomment)
282  !
283 END IF
284 !
285 !
286 !* 8.5 Surface humidity
287 ! ----------------
288 !
289 IF (dgs%LSURF_VARS) THEN
290  yrecfm='QS_SEAICE'
291  ycomment='X_Y_'//yrecfm//' (KG/KG)'
292  !
293  CALL write_surf(dgu, u, &
294  hprogram,yrecfm,dgs%XQS_ICE(:),iresp,hcomment=ycomment)
295  !
296 ENDIF
297 !
298 
299 !
300 !* 8.6. parameters at 2 and 10 meters :
301 ! -----------------------------
302 !
303 IF (dgs%N2M>=1) THEN
304  !
305  yrecfm='T2M_SEAICE'
306  ycomment='X_Y_'//yrecfm//' (K)'
307  !
308  CALL write_surf(dgu, u, &
309  hprogram,yrecfm,dgs%XT2M_ICE(:),iresp,hcomment=ycomment)
310  !
311  yrecfm='Q2M_SEAICE'
312  ycomment='X_Y_'//yrecfm//' (KG/KG)'
313  !
314  CALL write_surf(dgu, u, &
315  hprogram,yrecfm,dgs%XQ2M_ICE(:),iresp,hcomment=ycomment)
316  !
317  yrecfm='HU2M_SEAICE'
318  ycomment='X_Y_'//yrecfm//' (-)'
319  !
320  CALL write_surf(dgu, u, &
321  hprogram,yrecfm,dgs%XHU2M_ICE(:),iresp,hcomment=ycomment)
322  !
323  yrecfm='ZON10M_SEAICE'
324  ycomment='X_Y_'//yrecfm//' (M/S)'
325  !
326  CALL write_surf(dgu, u, &
327  hprogram,yrecfm,dgs%XZON10M_ICE(:),iresp,hcomment=ycomment)
328  !
329  yrecfm='MER10M_SEAICE'
330  ycomment='X_Y_'//yrecfm//' (M/S)'
331  !
332  CALL write_surf(dgu, u, &
333  hprogram,yrecfm,dgs%XMER10M_ICE(:),iresp,hcomment=ycomment)
334  !
335  yrecfm='W10M_SEAICE'
336  ycomment='X_Y_'//yrecfm//' (M/S)'
337  !
338  CALL write_surf(dgu, u, &
339  hprogram,yrecfm,dgs%XWIND10M_ICE(:),iresp,hcomment=ycomment)
340  !
341 END IF
342 !
343 ! End of IO
344 !
345  CALL end_io_surf_n(hprogram)
346 
347 IF (lhook) CALL dr_hook('WRITE_DIAG_SEB_SEAICE_N',1,zhook_handle)
348 !
349 !
350 END SUBROUTINE write_diag_seb_seaice_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_seaice_n(DTCO, DGU, U, DGS, DGSI, S, HPROGRAM)