source: LMDZ5/branches/testing/libf/phylmd/phys_output_write_mod.F90 @ 1881

Last change on this file since 1881 was 1864, checked in by Laurent Fairhead, 12 years ago

Création d'une nouvelle testing:

merge des modifications du trunk entre r1796 et r1860


New testing version

merged modifications between r1796 and r1860 from the trunk

i.e.
svn merge -r1796:1860 http://svn.lmd.jussieu.fr/LMDZ/LMDZ5/trunk

File size: 40.5 KB
Line 
1!
2! $Header$
3!
4MODULE phys_output_write_mod
5
6    USE phytrac_mod, ONLY : d_tr_cl, d_tr_th, d_tr_cv, d_tr_lessi_impa, &
7        d_tr_lessi_nucl, d_tr_insc, d_tr_bcscav, d_tr_evapls, d_tr_ls,  &
8        d_tr_trsp, d_tr_sscav, d_tr_sat, d_tr_uscav
9
10
11! Author: Abderrahmane IDELKADI (original include file)
12! Author: Laurent FAIRHEAD (transformation to module/subroutine)
13! Author: Ulysse GERARD (effective implementation)
14
15
16   CONTAINS
17     
18! ug Routine pour définir (los du premier passageà) ET sortir les variables
19    SUBROUTINE phys_output_write(itap, pdtphys, paprs, pphis, &
20   &                  pplay, lmax_th, aerosol_couple,         &
21   &                  ok_ade, ok_aie, ivap, new_aod, ok_sync, &
22   &                  ptconv, read_climoz, clevSTD, freq_moyNMC, ptconvth, &
23   &                  d_t, qx, d_qx, zmasse, flag_aerosol_strat)
24
25! This subroutine does the actual writing of diagnostics that were
26! defined and initialised in phys_output_mod.F90
27
28    USE dimphy
29    USE control_mod
30    USE phys_output_ctrlout_mod
31    USE phys_state_var_mod
32    USE phys_local_var_mod
33    USE indice_sol_mod
34    USE infotrac
35    USE comgeomphy
36    USE surface_data,     ONLY : type_ocean, ok_veget
37    USE aero_mod
38    USE ioipsl
39    USE write_field_phy
40    USE iophy
41    USE mod_phys_lmdz_para
42    USE netcdf,  ONLY : nf90_fill_real
43
44#ifdef CPP_XIOS
45    ! ug Pour les sorties XIOS
46        USE wxios
47    USE xios
48#endif
49
50    IMPLICIT NONE
51
52    INCLUDE "temps.h"
53    INCLUDE "clesphys.h"
54    INCLUDE "thermcell.h"
55    INCLUDE "compbl.h"
56    INCLUDE "YOMCST.h"
57    INCLUDE "dimensions.h"
58
59! Input
60    INTEGER :: itap, ivap, read_climoz
61    INTEGER, DIMENSION(klon) :: lmax_th
62    LOGICAL :: aerosol_couple, ok_sync
63    LOGICAL :: ok_ade, ok_aie, new_aod
64    LOGICAL, DIMENSION(klon, klev) :: ptconv, ptconvth
65    REAL :: pdtphys
66    CHARACTER (LEN=4), DIMENSION(nlevSTD) :: clevSTD
67    REAL, DIMENSION(klon) :: pphis
68    REAL, DIMENSION(klon, klev) :: pplay, d_t
69    REAL, DIMENSION(klon, klev+1) :: paprs
70    REAL, DIMENSION(klon,klev,nqtot) :: qx, d_qx
71    REAL, DIMENSION(klon, llm) :: zmasse
72    LOGICAL :: flag_aerosol_strat
73    REAL, DIMENSION(3) :: freq_moyNMC
74
75! Local
76    INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm
77    INTEGER :: itau_w
78    INTEGER :: i, iinit, iinitend=1, iff, iq, nsrf, k, ll, naero
79    REAL, DIMENSION (klon) :: zx_tmp_fi2d
80    REAL, DIMENSION (klon,klev) :: zx_tmp_fi3d, zpt_conv
81    REAL, DIMENSION (klon,klev+1) :: zx_tmp_fi3d1
82    CHARACTER (LEN=4)              :: bb2
83    INTEGER, DIMENSION(iim*jjmp1)  :: ndex2d
84    INTEGER, DIMENSION(iim*jjmp1*klev) :: ndex3d
85    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
86    REAL, PARAMETER :: missing_val=nf90_fill_real
87
88     ! On calcul le nouveau tau:
89     itau_w = itau_phy + itap + start_time * day_step / iphysiq
90     ! On le donne à iophy pour que les histwrite y aient accès:
91     CALL set_itau_iophy(itau_w)
92   
93    IF(.NOT.vars_defined) THEN
94        iinitend = 2
95    ELSE
96        iinitend = 1
97    ENDIF
98   
99! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
100DO iinit=1, iinitend
101#ifdef CPP_XIOS
102IF (vars_defined) THEN
103     CALL wxios_update_calendar(itau_w)
104END IF
105#endif
106! On procède à l'écriture ou à la définition des nombreuses variables:
107!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
108      CALL histwrite_phy(o_phis, pphis)
109      CALL histwrite_phy(o_aire, airephy)
110
111IF (vars_defined) THEN
112      DO i=1, klon
113       zx_tmp_fi2d(i)=pctsrf(i,is_ter)+pctsrf(i,is_lic)
114      ENDDO
115ENDIF
116
117      CALL histwrite_phy(o_contfracATM, zx_tmp_fi2d)
118      CALL histwrite_phy(o_contfracOR, pctsrf(:,is_ter))
119      CALL histwrite_phy(o_aireTER, paire_ter)
120!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
121      CALL histwrite_phy(o_flat, zxfluxlat)
122      CALL histwrite_phy(o_slp, slp)
123      CALL histwrite_phy(o_tsol, zxtsol)
124      CALL histwrite_phy(o_t2m, zt2m)
125      CALL histwrite_phy(o_t2m_min, zt2m)
126      CALL histwrite_phy(o_t2m_max, zt2m)
127
128IF (vars_defined) THEN
129      DO i=1, klon
130       zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
131      ENDDO
132ENDIF
133      CALL histwrite_phy(o_wind10m, zx_tmp_fi2d)
134
135IF (vars_defined) THEN
136      DO i=1, klon
137       zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
138      ENDDO
139ENDIF
140      CALL histwrite_phy(o_wind10max, zx_tmp_fi2d)
141
142IF (vars_defined) THEN
143      DO i = 1, klon
144         zx_tmp_fi2d(i) = pctsrf(i,is_sic)
145      ENDDO
146ENDIF
147      CALL histwrite_phy(o_sicf, zx_tmp_fi2d)
148      CALL histwrite_phy(o_q2m, zq2m)
149      CALL histwrite_phy(o_ustar, zustar)
150      CALL histwrite_phy(o_u10m, zu10m)
151      CALL histwrite_phy(o_v10m, zv10m)
152
153IF (vars_defined) THEN
154      DO i = 1, klon
155         zx_tmp_fi2d(i) = paprs(i,1)
156      ENDDO
157ENDIF
158      CALL histwrite_phy(o_psol, zx_tmp_fi2d)
159      CALL histwrite_phy(o_mass, zmasse)
160      CALL histwrite_phy(o_qsurf, zxqsurf)
161
162IF (.NOT. ok_veget) THEN
163      CALL histwrite_phy(o_qsol, qsol)
164ENDIF
165
166IF (vars_defined) THEN
167       DO i = 1, klon
168         zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)
169       ENDDO
170ENDIF
171
172      CALL histwrite_phy(o_precip, zx_tmp_fi2d)
173      CALL histwrite_phy(o_ndayrain, nday_rain)
174
175IF (vars_defined) THEN
176       DO i = 1, klon
177         zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)
178       ENDDO
179ENDIF
180      CALL histwrite_phy(o_plul, zx_tmp_fi2d)
181
182IF (vars_defined) THEN
183      DO i = 1, klon
184         zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)
185      ENDDO
186ENDIF
187      CALL histwrite_phy(o_pluc, zx_tmp_fi2d)
188      CALL histwrite_phy(o_snow, snow_fall)
189      CALL histwrite_phy(o_msnow, snow_o)
190      CALL histwrite_phy(o_fsnow, zfra_o)
191      CALL histwrite_phy(o_evap, evap)
192      CALL histwrite_phy(o_tops, topsw)
193      CALL histwrite_phy(o_tops0, topsw0)
194      CALL histwrite_phy(o_topl, toplw)
195      CALL histwrite_phy(o_topl0, toplw0)
196
197IF (vars_defined) THEN
198      zx_tmp_fi2d(1 : klon) = swup ( 1 : klon, klevp1 )
199ENDIF
200      CALL histwrite_phy(o_SWupTOA, zx_tmp_fi2d)
201
202IF (vars_defined) THEN
203      zx_tmp_fi2d(1 : klon) = swup0 ( 1 : klon, klevp1 )
204ENDIF
205      CALL histwrite_phy(o_SWupTOAclr, zx_tmp_fi2d)
206
207IF (vars_defined) THEN
208      zx_tmp_fi2d(1 : klon) = swdn ( 1 : klon, klevp1 )
209ENDIF
210      CALL histwrite_phy(o_SWdnTOA, zx_tmp_fi2d)
211
212IF (vars_defined) THEN
213      zx_tmp_fi2d(1 : klon) = swdn0 ( 1 : klon, klevp1 )
214ENDIF
215      CALL histwrite_phy(o_SWdnTOAclr, zx_tmp_fi2d)
216
217IF (vars_defined) THEN
218      zx_tmp_fi2d(:) = topsw(:)-toplw(:)
219ENDIF
220      CALL histwrite_phy(o_nettop, zx_tmp_fi2d)
221      CALL histwrite_phy(o_SWup200, SWup200)
222      CALL histwrite_phy(o_SWup200clr, SWup200clr)
223      CALL histwrite_phy(o_SWdn200, SWdn200)
224      CALL histwrite_phy(o_SWdn200clr, SWdn200clr)
225      CALL histwrite_phy(o_LWup200, LWup200)
226      CALL histwrite_phy(o_LWup200clr, LWup200clr)
227      CALL histwrite_phy(o_LWdn200, LWdn200)
228      CALL histwrite_phy(o_LWdn200clr, LWdn200clr)
229      CALL histwrite_phy(o_sols, solsw)
230      CALL histwrite_phy(o_sols0, solsw0)
231      CALL histwrite_phy(o_soll, sollw)
232      CALL histwrite_phy(o_radsol, radsol)
233      CALL histwrite_phy(o_soll0, sollw0)
234
235IF (vars_defined) THEN
236      zx_tmp_fi2d(1 : klon) = swup ( 1 : klon, 1 )
237ENDIF
238      CALL histwrite_phy(o_SWupSFC, zx_tmp_fi2d)
239
240IF (vars_defined) THEN
241      zx_tmp_fi2d(1 : klon) = swup0 ( 1 : klon, 1 )
242ENDIF
243      CALL histwrite_phy(o_SWupSFCclr, zx_tmp_fi2d)
244
245IF (vars_defined) THEN
246      zx_tmp_fi2d(1 : klon) = swdn ( 1 : klon, 1 )
247ENDIF
248      CALL histwrite_phy(o_SWdnSFC, zx_tmp_fi2d)
249
250IF (vars_defined) THEN
251      zx_tmp_fi2d(1 : klon) = swdn0 ( 1 : klon, 1 )
252ENDIF
253      CALL histwrite_phy(o_SWdnSFCclr, zx_tmp_fi2d)
254
255IF (vars_defined) THEN
256      zx_tmp_fi2d(1:klon)=sollwdown(1:klon)-sollw(1:klon)
257ENDIF
258      CALL histwrite_phy(o_LWupSFC, zx_tmp_fi2d)
259      CALL histwrite_phy(o_LWdnSFC, sollwdown)
260
261IF (vars_defined) THEN
262       sollwdownclr(1:klon) = -1.*lwdn0(1:klon,1)
263      zx_tmp_fi2d(1:klon)=sollwdownclr(1:klon)-sollw0(1:klon)
264ENDIF
265      CALL histwrite_phy(o_LWupSFCclr, zx_tmp_fi2d)
266      CALL histwrite_phy(o_LWdnSFCclr, sollwdownclr)
267      CALL histwrite_phy(o_bils, bils)
268      CALL histwrite_phy(o_bils_diss, bils_diss)
269      CALL histwrite_phy(o_bils_ec, bils_ec)
270      CALL histwrite_phy(o_bils_tke, bils_tke)
271      CALL histwrite_phy(o_bils_kinetic, bils_kinetic)
272      CALL histwrite_phy(o_bils_latent, bils_latent)
273      CALL histwrite_phy(o_bils_enthalp, bils_enthalp)
274
275IF (vars_defined) THEN
276      zx_tmp_fi2d(1:klon)=-1*sens(1:klon)
277ENDIF
278      CALL histwrite_phy(o_sens, zx_tmp_fi2d)
279      CALL histwrite_phy(o_fder, fder)
280      CALL histwrite_phy(o_ffonte, zxffonte)
281      CALL histwrite_phy(o_fqcalving, zxfqcalving)
282      CALL histwrite_phy(o_fqfonte, zxfqfonte)
283IF (vars_defined) THEN
284      zx_tmp_fi2d=0.
285      DO nsrf=1,nbsrf
286        zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxu(:,1,nsrf)
287      ENDDO
288ENDIF
289      CALL histwrite_phy(o_taux, zx_tmp_fi2d)
290
291IF (vars_defined) THEN
292      zx_tmp_fi2d=0.
293      DO nsrf=1,nbsrf
294          zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxv(:,1,nsrf)
295      ENDDO
296ENDIF
297      CALL histwrite_phy(o_tauy, zx_tmp_fi2d)
298
299
300         DO nsrf = 1, nbsrf
301IF (vars_defined)             zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100.
302      CALL histwrite_phy(o_pourc_srf(nsrf), zx_tmp_fi2d)
303IF (vars_defined)           zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)
304      CALL histwrite_phy(o_fract_srf(nsrf), zx_tmp_fi2d)
305IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf)
306      CALL histwrite_phy(o_taux_srf(nsrf), zx_tmp_fi2d)
307IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf)
308      CALL histwrite_phy(o_tauy_srf(nsrf), zx_tmp_fi2d)
309IF (vars_defined)         zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf)
310      CALL histwrite_phy(o_tsol_srf(nsrf), zx_tmp_fi2d)
311IF (vars_defined)         zx_tmp_fi2d(1 : klon) = evap_pot( 1 : klon, nsrf)
312      CALL histwrite_phy(o_evappot_srf(nsrf), zx_tmp_fi2d)
313IF (vars_defined)       zx_tmp_fi2d(1 : klon) = ustar(1 : klon, nsrf)
314      CALL histwrite_phy(o_ustar_srf(nsrf), zx_tmp_fi2d)
315IF (vars_defined)       zx_tmp_fi2d(1 : klon) = u10m(1 : klon, nsrf)
316      CALL histwrite_phy(o_u10m_srf(nsrf), zx_tmp_fi2d)
317IF (vars_defined)       zx_tmp_fi2d(1 : klon) = v10m(1 : klon, nsrf)
318      CALL histwrite_phy(o_v10m_srf(nsrf), zx_tmp_fi2d)
319IF (vars_defined)       zx_tmp_fi2d(1 : klon) = t2m(1 : klon, nsrf)
320      CALL histwrite_phy(o_t2m_srf(nsrf), zx_tmp_fi2d)
321IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fevap(1 : klon, nsrf)
322      CALL histwrite_phy(o_evap_srf(nsrf), zx_tmp_fi2d)
323IF (vars_defined)        zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf)
324      CALL histwrite_phy(o_sens_srf(nsrf), zx_tmp_fi2d)
325IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf)
326      CALL histwrite_phy(o_lat_srf(nsrf), zx_tmp_fi2d)
327IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fsollw( 1 : klon, nsrf)
328      CALL histwrite_phy(o_flw_srf(nsrf), zx_tmp_fi2d)
329IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, nsrf)
330      CALL histwrite_phy(o_fsw_srf(nsrf), zx_tmp_fi2d)
331IF (vars_defined)         zx_tmp_fi2d(1 : klon) = wfbils( 1 : klon, nsrf)
332      CALL histwrite_phy(o_wbils_srf(nsrf), zx_tmp_fi2d)
333IF (vars_defined)         zx_tmp_fi2d(1 : klon) = wfbilo( 1 : klon, nsrf)
334      CALL histwrite_phy(o_wbilo_srf(nsrf), zx_tmp_fi2d)
335
336      IF (iflag_pbl > 1) THEN
337      CALL histwrite_phy(o_tke_srf(nsrf),  pbl_tke(:,1:klev,nsrf))
338      CALL histwrite_phy(o_tke_max_srf(nsrf),  pbl_tke(:,1:klev,nsrf))
339      ENDIF
340
341      ENDDO
342      DO nsrf=1,nbsrf+1
343         CALL histwrite_phy(o_wstar(nsrf), wstar(1 : klon, nsrf))
344      ENDDO
345
346      CALL histwrite_phy(o_cdrm, cdragm)
347      CALL histwrite_phy(o_cdrh, cdragh)
348      CALL histwrite_phy(o_cldl, cldl)
349      CALL histwrite_phy(o_cldm, cldm)
350      CALL histwrite_phy(o_cldh, cldh)
351      CALL histwrite_phy(o_cldt, cldt)
352      CALL histwrite_phy(o_cldq, cldq)
353IF (vars_defined)       zx_tmp_fi2d(1:klon) = flwp(1:klon)
354      CALL histwrite_phy(o_lwp, zx_tmp_fi2d)
355IF (vars_defined)       zx_tmp_fi2d(1:klon) = fiwp(1:klon)
356      CALL histwrite_phy(o_iwp, zx_tmp_fi2d)
357      CALL histwrite_phy(o_ue, ue)
358      CALL histwrite_phy(o_ve, ve)
359      CALL histwrite_phy(o_uq, uq)
360      CALL histwrite_phy(o_vq, vq)
361      IF(iflag_con.GE.3) THEN ! sb
362      CALL histwrite_phy(o_cape, cape)
363      CALL histwrite_phy(o_pbase, ema_pcb)
364      CALL histwrite_phy(o_ptop, ema_pct)
365      CALL histwrite_phy(o_fbase, ema_cbmf)
366        if (iflag_con /= 30) then
367      CALL histwrite_phy(o_plcl, plcl)
368      CALL histwrite_phy(o_plfc, plfc)
369      CALL histwrite_phy(o_wbeff, wbeff)
370        end if
371
372      CALL histwrite_phy(o_cape_max, cape)
373
374      CALL histwrite_phy(o_upwd, upwd)
375      CALL histwrite_phy(o_Ma, Ma)
376      CALL histwrite_phy(o_dnwd, dnwd)
377      CALL histwrite_phy(o_dnwd0, dnwd0)
378IF (vars_defined)         zx_tmp_fi2d=float(itau_con)/float(itap)
379      CALL histwrite_phy(o_ftime_con, zx_tmp_fi2d)
380IF (vars_defined) THEN
381      IF(iflag_thermals>=1)THEN
382         zx_tmp_fi3d=dnwd+dnwd0+upwd+fm_therm(:,1:klev)
383      ELSE
384         zx_tmp_fi3d=dnwd+dnwd0+upwd
385      ENDIF
386ENDIF
387      CALL histwrite_phy(o_mc, zx_tmp_fi3d)
388      ENDIF !iflag_con .GE. 3
389      CALL histwrite_phy(o_prw, prw)
390      CALL histwrite_phy(o_s_pblh, s_pblh)
391      CALL histwrite_phy(o_s_pblt, s_pblt)
392      CALL histwrite_phy(o_s_lcl, s_lcl)
393      CALL histwrite_phy(o_s_therm, s_therm)
394!IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
395!       IF (o_s_capCL%flag(iff)<=lev_files(iff)) THEN
396!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
397!    $o_s_capCL%name,itau_w,s_capCL)
398!       ENDIF
399!       IF (o_s_oliqCL%flag(iff)<=lev_files(iff)) THEN
400!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
401!    $o_s_oliqCL%name,itau_w,s_oliqCL)
402!       ENDIF
403!       IF (o_s_cteiCL%flag(iff)<=lev_files(iff)) THEN
404!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
405!    $o_s_cteiCL%name,itau_w,s_cteiCL)
406!       ENDIF
407!       IF (o_s_trmb1%flag(iff)<=lev_files(iff)) THEN
408!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
409!    $o_s_trmb1%name,itau_w,s_trmb1)
410!       ENDIF
411!       IF (o_s_trmb2%flag(iff)<=lev_files(iff)) THEN
412!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
413!    $o_s_trmb2%name,itau_w,s_trmb2)
414!       ENDIF
415!       IF (o_s_trmb3%flag(iff)<=lev_files(iff)) THEN
416!     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
417!    $o_s_trmb3%name,itau_w,s_trmb3)
418!       ENDIF
419
420
421
422! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
423! Champs interpolles sur des niveaux de pression
424      DO iff=1, nfiles
425        ll=0
426        DO k=1, nlevSTD
427         bb2=clevSTD(k)
428         IF(bb2.EQ."850".OR.bb2.EQ."700".OR. &
429            bb2.EQ."500".OR.bb2.EQ."200".OR. &
430            bb2.EQ."100".OR. &
431            bb2.EQ."50".OR.bb2.EQ."10") THEN
432
433! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
434          ll=ll+1
435      CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
436      CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
437      CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
438      CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
439      CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
440      CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
441
442       ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
443       ENDDO
444       ENDDO
445
446
447
448IF (vars_defined) THEN
449      DO i=1, klon
450       IF (pctsrf(i,is_oce).GT.epsfra.OR. &
451           pctsrf(i,is_sic).GT.epsfra) THEN
452        zx_tmp_fi2d(i) = (ftsol(i, is_oce) * pctsrf(i,is_oce)+ &
453                         ftsol(i, is_sic) * pctsrf(i,is_sic))/ &
454                         (pctsrf(i,is_oce)+pctsrf(i,is_sic))
455       ELSE
456        zx_tmp_fi2d(i) = 273.15
457       ENDIF
458      ENDDO
459ENDIF
460      CALL histwrite_phy(o_t_oce_sic, zx_tmp_fi2d)
461
462! Couplage convection-couche limite
463      IF (iflag_con.GE.3) THEN
464      IF (iflag_coupl>=1) THEN
465      CALL histwrite_phy(o_ale_bl, ale_bl)
466      CALL histwrite_phy(o_alp_bl, alp_bl)
467      ENDIF !iflag_coupl>=1
468      ENDIF !(iflag_con.GE.3)
469! Wakes
470      IF (iflag_con.EQ.3) THEN
471      IF (iflag_wake>=1) THEN
472      CALL histwrite_phy(o_ale_wk, ale_wake)
473      CALL histwrite_phy(o_alp_wk, alp_wake)
474      CALL histwrite_phy(o_ale, ale)
475      CALL histwrite_phy(o_alp, alp)
476      CALL histwrite_phy(o_cin, cin)
477      CALL histwrite_phy(o_WAPE, wake_pe)
478      CALL histwrite_phy(o_wake_h, wake_h)
479      CALL histwrite_phy(o_wake_s, wake_s)
480      CALL histwrite_phy(o_wake_deltat, wake_deltat)
481      CALL histwrite_phy(o_wake_deltaq, wake_deltaq)
482      CALL histwrite_phy(o_wake_omg, wake_omg)
483IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_wake(1:klon,1:klev) &
484                                              /pdtphys
485      CALL histwrite_phy(o_dtwak, zx_tmp_fi3d)
486IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_wake(1:klon,1:klev)/pdtphys
487      CALL histwrite_phy(o_dqwak, zx_tmp_fi3d)
488      ENDIF ! iflag_wake>=1
489      CALL histwrite_phy(o_Vprecip, Vprecip)
490      CALL histwrite_phy(o_ftd, ftd)
491      CALL histwrite_phy(o_fqd, fqd)
492      ELSEIF (iflag_con.EQ.30) THEN
493! sortie RomP convection descente insaturee iflag_con=30
494      CALL histwrite_phy(o_Vprecip, Vprecip)
495      CALL histwrite_phy(o_wdtrainA, wdtrainA)
496      CALL histwrite_phy(o_wdtrainM, wdtrainM)
497      ENDIF !(iflag_con.EQ.3.or.iflag_con.EQ.30)
498!!! nrlmd le 10/04/2012
499        IF (iflag_trig_bl>=1) THEN
500      CALL histwrite_phy(o_n2, n2)
501      CALL histwrite_phy(o_s2, s2)
502      CALL histwrite_phy(o_proba_notrig, proba_notrig)
503      CALL histwrite_phy(o_random_notrig, random_notrig)
504      CALL histwrite_phy(o_ale_bl_stat, ale_bl_stat)
505      CALL histwrite_phy(o_ale_bl_trig, ale_bl_trig)
506       ENDIF  !(iflag_trig_bl>=1)
507        IF (iflag_clos_bl>=1) THEN
508      CALL histwrite_phy(o_alp_bl_det, alp_bl_det)
509      CALL histwrite_phy(o_alp_bl_fluct_m, alp_bl_fluct_m)
510      CALL histwrite_phy(o_alp_bl_fluct_tke,  &
511       alp_bl_fluct_tke)
512      CALL histwrite_phy(o_alp_bl_conv, alp_bl_conv)
513      CALL histwrite_phy(o_alp_bl_stat, alp_bl_stat)
514       ENDIF  !(iflag_clos_bl>=1)
515!!! fin nrlmd le 10/04/2012
516      IF (type_ocean=='slab ') THEN
517      CALL histwrite_phy(o_slab_bils, slab_wfbils)
518      ENDIF !type_ocean == force/slab
519      CALL histwrite_phy(o_weakinv, weak_inversion)
520      CALL histwrite_phy(o_dthmin, dthmin)
521      CALL histwrite_phy(o_cldtau, cldtau)
522      CALL histwrite_phy(o_cldemi, cldemi)
523      CALL histwrite_phy(o_pr_con_l, pmflxr(:,1:klev))
524      CALL histwrite_phy(o_pr_con_i, pmflxs(:,1:klev))
525      CALL histwrite_phy(o_pr_lsc_l, prfl(:,1:klev))
526      CALL histwrite_phy(o_pr_lsc_i, psfl(:,1:klev))
527      CALL histwrite_phy(o_re, re)
528      CALL histwrite_phy(o_fl, fl)
529IF (vars_defined) THEN
530      DO i=1, klon
531       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
532      ENDDO
533ENDIF
534      CALL histwrite_phy(o_rh2m, zx_tmp_fi2d)
535
536IF (vars_defined) THEN
537      DO i=1, klon
538       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
539      ENDDO
540ENDIF
541      CALL histwrite_phy(o_rh2m_min, zx_tmp_fi2d)
542
543IF (vars_defined) THEN
544      DO i=1, klon
545       zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
546      ENDDO
547ENDIF
548      CALL histwrite_phy(o_rh2m_max, zx_tmp_fi2d)
549
550      CALL histwrite_phy(o_qsat2m, qsat2m)
551      CALL histwrite_phy(o_tpot, tpot)
552      CALL histwrite_phy(o_tpote, tpote)
553IF (vars_defined) zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, is_ter)
554      CALL histwrite_phy(o_SWnetOR,  zx_tmp_fi2d)
555IF (vars_defined) zx_tmp_fi2d(1:klon) = solsw(1:klon)/(1.-albsol1(1:klon))
556      CALL histwrite_phy(o_SWdownOR,  zx_tmp_fi2d)
557      CALL histwrite_phy(o_LWdownOR, sollwdown)
558      CALL histwrite_phy(o_snowl, snow_lsc)
559      CALL histwrite_phy(o_solldown, sollwdown)
560      CALL histwrite_phy(o_dtsvdfo, d_ts(:,is_oce))
561      CALL histwrite_phy(o_dtsvdft, d_ts(:,is_ter))
562      CALL histwrite_phy(o_dtsvdfg,  d_ts(:,is_lic))
563      CALL histwrite_phy(o_dtsvdfi, d_ts(:,is_sic))
564      CALL histwrite_phy(o_rugs, zxrugs)
565! OD550 per species
566      IF (new_aod .and. (.not. aerosol_couple)) THEN
567          IF (ok_ade.OR.ok_aie) THEN
568      CALL histwrite_phy(o_od550aer, od550aer)
569      CALL histwrite_phy(o_od865aer, od865aer)
570      CALL histwrite_phy(o_absvisaer, absvisaer)
571      CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
572      CALL histwrite_phy(o_sconcso4, sconcso4)
573      CALL histwrite_phy(o_sconcoa, sconcoa)
574      CALL histwrite_phy(o_sconcbc, sconcbc)
575      CALL histwrite_phy(o_sconcss, sconcss)
576      CALL histwrite_phy(o_sconcdust, sconcdust)
577      CALL histwrite_phy(o_concso4, concso4)
578      CALL histwrite_phy(o_concoa, concoa)
579      CALL histwrite_phy(o_concbc, concbc)
580      CALL histwrite_phy(o_concss, concss)
581      CALL histwrite_phy(o_concdust, concdust)
582      CALL histwrite_phy(o_loadso4, loadso4)
583      CALL histwrite_phy(o_loadoa, loadoa)
584      CALL histwrite_phy(o_loadbc, loadbc)
585      CALL histwrite_phy(o_loadss, loadss)
586      CALL histwrite_phy(o_loaddust, loaddust)
587!--STRAT AER
588          ENDIF
589          IF (ok_ade.OR.ok_aie.OR.flag_aerosol_strat) THEN
590          DO naero = 1, naero_spc
591      CALL histwrite_phy(o_tausumaero(naero), &
592       tausum_aero(:,2,naero) )
593          END DO
594          ENDIF
595      ENDIF
596       IF (ok_ade) THEN
597      CALL histwrite_phy(o_topswad, topswad_aero)
598      CALL histwrite_phy(o_topswad0, topswad0_aero)
599      CALL histwrite_phy(o_solswad, solswad_aero)
600      CALL histwrite_phy(o_solswad0, solswad0_aero)
601!====MS forcing diagnostics
602        if (new_aod) then
603      CALL histwrite_phy(o_swtoaas_nat, topsw_aero(:,1))
604      CALL histwrite_phy(o_swsrfas_nat, solsw_aero(:,1))
605      CALL histwrite_phy(o_swtoacs_nat, topsw0_aero(:,1))
606      CALL histwrite_phy(o_swsrfcs_nat, solsw0_aero(:,1))
607!ant
608      CALL histwrite_phy(o_swtoaas_ant, topsw_aero(:,2))
609      CALL histwrite_phy(o_swsrfas_ant, solsw_aero(:,2))
610      CALL histwrite_phy(o_swtoacs_ant, topsw0_aero(:,2))
611      CALL histwrite_phy(o_swsrfcs_ant, solsw0_aero(:,2))
612!cf
613        if (.not. aerosol_couple) then
614      CALL histwrite_phy(o_swtoacf_nat, topswcf_aero(:,1))
615      CALL histwrite_phy(o_swsrfcf_nat, solswcf_aero(:,1))
616      CALL histwrite_phy(o_swtoacf_ant, topswcf_aero(:,2))
617      CALL histwrite_phy(o_swsrfcf_ant, solswcf_aero(:,2))
618      CALL histwrite_phy(o_swtoacf_zero,topswcf_aero(:,3))
619      CALL histwrite_phy(o_swsrfcf_zero,solswcf_aero(:,3))
620        endif
621    endif ! new_aod
622!====MS forcing diagnostics
623       ENDIF
624       IF (ok_aie) THEN
625      CALL histwrite_phy(o_topswai, topswai_aero)
626      CALL histwrite_phy(o_solswai, solswai_aero)
627      CALL histwrite_phy(o_scdnc, scdnc)
628      CALL histwrite_phy(o_cldncl, cldncl)
629      CALL histwrite_phy(o_reffclws, reffclws)
630      CALL histwrite_phy(o_reffclwc, reffclwc)
631      CALL histwrite_phy(o_cldnvi, cldnvi)
632      CALL histwrite_phy(o_lcc, lcc)
633      CALL histwrite_phy(o_lcc3d, lcc3d)
634      CALL histwrite_phy(o_lcc3dcon, lcc3dcon)
635      CALL histwrite_phy(o_lcc3dstra, lcc3dstra)
636      CALL histwrite_phy(o_reffclwtop, reffclwtop)
637       ENDIF
638! Champs 3D:
639       IF (ok_ade .OR. ok_aie) then
640      CALL histwrite_phy(o_ec550aer, ec550aer)
641       ENDIF
642      CALL histwrite_phy(o_lwcon, flwc)
643      CALL histwrite_phy(o_iwcon, fiwc)
644      CALL histwrite_phy(o_temp, t_seri)
645      CALL histwrite_phy(o_theta, theta)
646      CALL histwrite_phy(o_ovapinit, qx(:,:,ivap))
647      CALL histwrite_phy(o_ovap, q_seri)
648      CALL histwrite_phy(o_oliq, ql_seri)
649      CALL histwrite_phy(o_geop, zphi)
650      CALL histwrite_phy(o_vitu, u_seri)
651      CALL histwrite_phy(o_vitv, v_seri)
652      CALL histwrite_phy(o_vitw, omega)
653      CALL histwrite_phy(o_pres, pplay)
654      CALL histwrite_phy(o_paprs, paprs(:,1:klev))
655IF (vars_defined) THEN
656         DO i=1, klon
657          zx_tmp_fi3d1(i,1)= pphis(i)/RG
658!020611   zx_tmp_fi3d(i,1)= pphis(i)/RG
659         ENDDO
660         DO k=1, klev
661!020611        DO k=1, klev-1
662         DO i=1, klon
663!020611         zx_tmp_fi3d(i,k+1)= zx_tmp_fi3d(i,k) - (t_seri(i,k) *RD *
664          zx_tmp_fi3d1(i,k+1)= zx_tmp_fi3d1(i,k) - (t_seri(i,k) *RD *  &
665          (paprs(i,k+1) - paprs(i,k))) / ( pplay(i,k) * RG )
666         ENDDO
667         ENDDO
668ENDIF
669      CALL histwrite_phy(o_zfull,zx_tmp_fi3d1(:,2:klevp1))
670!020611    $o_zfull%name,itau_w,zx_tmp_fi3d)
671
672IF (vars_defined)  THEN
673         DO i=1, klon
674          zx_tmp_fi3d(i,1)= pphis(i)/RG - ( &
675          (t_seri(i,1)+zxtsol(i))/2. *RD * &
676          (pplay(i,1) - paprs(i,1)))/( (paprs(i,1)+pplay(i,1))/2.* RG)
677         ENDDO
678         DO k=1, klev-1
679         DO i=1, klon
680          zx_tmp_fi3d(i,k+1)= zx_tmp_fi3d(i,k) - ( &
681          (t_seri(i,k)+t_seri(i,k+1))/2. *RD *  &
682          (pplay(i,k+1) - pplay(i,k))) / ( paprs(i,k) * RG )
683         ENDDO
684         ENDDO
685ENDIF
686      CALL histwrite_phy(o_zhalf, zx_tmp_fi3d)
687      CALL histwrite_phy(o_rneb, cldfra)
688      CALL histwrite_phy(o_rnebcon, rnebcon)
689      CALL histwrite_phy(o_rnebls, rneb)
690      CALL histwrite_phy(o_rhum, zx_rh)
691      CALL histwrite_phy(o_ozone, &
692       wo(:, :, 1) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
693
694      IF (read_climoz == 2) THEN
695      CALL histwrite_phy(o_ozone_light, &
696       wo(:, :, 2) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
697      ENDIF
698
699      CALL histwrite_phy(o_dtphy, d_t)
700      CALL histwrite_phy(o_dqphy,  d_qx(:,:,ivap))
701        DO nsrf=1, nbsrf
702IF (vars_defined) zx_tmp_fi2d(1 : klon) = falb1( 1 : klon, nsrf)
703      CALL histwrite_phy(o_albe_srf(nsrf), zx_tmp_fi2d)
704IF (vars_defined) zx_tmp_fi2d(1 : klon) = frugs( 1 : klon, nsrf)
705      CALL histwrite_phy(o_rugs_srf(nsrf), zx_tmp_fi2d)
706IF (vars_defined) zx_tmp_fi2d(1 : klon) = agesno( 1 : klon, nsrf)
707      CALL histwrite_phy(o_ages_srf(nsrf), zx_tmp_fi2d)
708        ENDDO !nsrf=1, nbsrf
709      CALL histwrite_phy(o_alb1, albsol1)
710      CALL histwrite_phy(o_alb2, albsol2)
711!FH Sorties pour la couche limite
712      if (iflag_pbl>1) then
713      zx_tmp_fi3d=0.
714IF (vars_defined) THEN
715      do nsrf=1,nbsrf
716         do k=1,klev
717          zx_tmp_fi3d(:,k)=zx_tmp_fi3d(:,k) &
718          +pctsrf(:,nsrf)*pbl_tke(:,k,nsrf)
719         enddo
720      enddo
721ENDIF
722      CALL histwrite_phy(o_tke, zx_tmp_fi3d)
723
724      CALL histwrite_phy(o_tke_max, zx_tmp_fi3d)
725      ENDIF
726
727      CALL histwrite_phy(o_kz, coefh(:,:,is_ave))
728
729      CALL histwrite_phy(o_kz_max, coefh(:,:,is_ave))
730
731      CALL histwrite_phy(o_clwcon, clwcon0)
732      CALL histwrite_phy(o_dtdyn, d_t_dyn)
733      CALL histwrite_phy(o_dqdyn, d_q_dyn)
734      CALL histwrite_phy(o_dudyn, d_u_dyn)
735      CALL histwrite_phy(o_dvdyn, d_v_dyn)
736
737IF (vars_defined) THEN
738      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys
739ENDIF
740      CALL histwrite_phy(o_dtcon, zx_tmp_fi3d)
741      if(iflag_thermals.eq.1)then
742IF (vars_defined) THEN
743      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
744                                 d_t_ajsb(1:klon,1:klev)/pdtphys
745ENDIF
746      CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
747      else if(iflag_thermals.gt.1.and.iflag_wake.EQ.1)then
748IF (vars_defined) THEN
749      zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
750                                 d_t_ajs(1:klon,1:klev)/pdtphys + &
751                                 d_t_wake(1:klon,1:klev)/pdtphys
752ENDIF
753      CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
754      endif
755IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_con(1:klon,1:klev)/pdtphys
756      CALL histwrite_phy(o_ducon, zx_tmp_fi3d)
757IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_con(1:klon,1:klev)/pdtphys
758      CALL histwrite_phy(o_dvcon, zx_tmp_fi3d)
759IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
760      CALL histwrite_phy(o_dqcon, zx_tmp_fi3d)
761
762      IF(iflag_thermals.EQ.1) THEN
763IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
764        CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
765      ELSE IF(iflag_thermals.GT.1.AND.iflag_wake.EQ.1) THEN
766IF (vars_defined) THEN
767         zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys + &
768                                     d_q_ajs(1:klon,1:klev)/pdtphys + &
769                                     d_q_wake(1:klon,1:klev)/pdtphys
770ENDIF
771         CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
772      ENDIF
773
774IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lsc(1:klon,1:klev)/pdtphys
775      CALL histwrite_phy(o_dtlsc, zx_tmp_fi3d)
776IF (vars_defined) zx_tmp_fi3d(1:klon, 1:klev)=(d_t_lsc(1:klon,1:klev)+ &
777                                 d_t_eva(1:klon,1:klev))/pdtphys
778      CALL histwrite_phy(o_dtlschr, zx_tmp_fi3d)
779IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys
780      CALL histwrite_phy(o_dqlsc, zx_tmp_fi3d)
781IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=beta_prec(1:klon,1:klev)
782      CALL histwrite_phy(o_beta_prec, zx_tmp_fi3d)
783!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
784! Sorties specifiques a la separation thermiques/non thermiques
785       if (iflag_thermals>=1) then
786IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lscth(1:klon,1:klev)/pdtphys
787      CALL histwrite_phy(o_dtlscth, zx_tmp_fi3d)
788IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lscst(1:klon,1:klev)/pdtphys
789      CALL histwrite_phy(o_dtlscst, zx_tmp_fi3d)
790IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lscth(1:klon,1:klev)/pdtphys
791      CALL histwrite_phy(o_dqlscth, zx_tmp_fi3d)
792IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lscst(1:klon,1:klev)/pdtphys
793      CALL histwrite_phy(o_dqlscst, zx_tmp_fi3d)
794      CALL histwrite_phy(o_plulth, plul_th)
795      CALL histwrite_phy(o_plulst, plul_st)
796IF (vars_defined) THEN
797      do k=1,klev
798      do i=1,klon
799          if (ptconvth(i,k)) then
800           zx_tmp_fi3d(i,k)=1.
801          else
802           zx_tmp_fi3d(i,k)=0.
803          endif
804      enddo
805      enddo
806ENDIF
807      CALL histwrite_phy(o_ptconvth, zx_tmp_fi3d)
808IF (vars_defined) THEN
809      do i=1,klon
810           zx_tmp_fi2d(1:klon)=lmax_th(:)
811      enddo
812ENDIF
813      CALL histwrite_phy(o_lmaxth, zx_tmp_fi2d)
814      endif ! iflag_thermals>=1
815!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
816IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_vdf(1:klon,1:klev)/pdtphys
817      CALL histwrite_phy(o_dtvdf, zx_tmp_fi3d)
818IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_diss(1:klon,1:klev)/pdtphys
819      CALL histwrite_phy(o_dtdis, zx_tmp_fi3d)
820IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_vdf(1:klon,1:klev)/pdtphys
821      CALL histwrite_phy(o_dqvdf, zx_tmp_fi3d)
822IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_eva(1:klon,1:klev)/pdtphys
823      CALL histwrite_phy(o_dteva, zx_tmp_fi3d)
824IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_eva(1:klon,1:klev)/pdtphys
825      CALL histwrite_phy(o_dqeva, zx_tmp_fi3d)
826      zpt_conv = 0.
827      WHERE (ptconv) zpt_conv = 1.
828      CALL histwrite_phy(o_ptconv, zpt_conv)
829      CALL histwrite_phy(o_ratqs, ratqs)
830IF (vars_defined) THEN
831      zx_tmp_fi3d(1:klon,1:klev)=d_t_ajs(1:klon,1:klev)/pdtphys - &
832                                 d_t_ajsb(1:klon,1:klev)/pdtphys
833ENDIF
834      CALL histwrite_phy(o_dtthe, zx_tmp_fi3d)
835       IF (iflag_thermals>=1) THEN
836! Pour l instant 0 a y reflichir pour les thermiques
837         zx_tmp_fi2d=0.
838      CALL histwrite_phy(o_ftime_th, zx_tmp_fi2d)
839      CALL histwrite_phy(o_f_th, fm_therm)
840      CALL histwrite_phy(o_e_th, entr_therm)
841      CALL histwrite_phy(o_w_th, zw2)
842      CALL histwrite_phy(o_q_th, zqasc)
843      CALL histwrite_phy(o_a_th, fraca)
844      CALL histwrite_phy(o_d_th, detr_therm)
845      CALL histwrite_phy(o_f0_th, f0)
846      CALL histwrite_phy(o_zmax_th, zmax_th)
847IF (vars_defined) THEN
848      zx_tmp_fi3d(1:klon,1:klev)=d_q_ajs(1:klon,1:klev)/pdtphys - &
849                                 d_q_ajsb(1:klon,1:klev)/pdtphys
850ENDIF
851      CALL histwrite_phy(o_dqthe, zx_tmp_fi3d)
852      ENDIF !iflag_thermals
853IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_ajsb(1:klon,1:klev)/pdtphys
854      CALL histwrite_phy(o_dtajs, zx_tmp_fi3d)
855IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_ajsb(1:klon,1:klev)/pdtphys
856      CALL histwrite_phy(o_dqajs, zx_tmp_fi3d)
857IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=heat(1:klon,1:klev)/RDAY
858      CALL histwrite_phy(o_dtswr, zx_tmp_fi3d)
859IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=heat0(1:klon,1:klev)/RDAY
860      CALL histwrite_phy(o_dtsw0, zx_tmp_fi3d)
861IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=-1.*cool(1:klon,1:klev)/RDAY
862      CALL histwrite_phy(o_dtlwr, zx_tmp_fi3d)
863IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=-1.*cool0(1:klon,1:klev)/RDAY
864      CALL histwrite_phy(o_dtlw0, zx_tmp_fi3d)
865IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_ec(1:klon,1:klev)/pdtphys
866      CALL histwrite_phy(o_dtec, zx_tmp_fi3d)
867IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_vdf(1:klon,1:klev)/pdtphys
868      CALL histwrite_phy(o_duvdf, zx_tmp_fi3d)
869IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_vdf(1:klon,1:klev)/pdtphys
870      CALL histwrite_phy(o_dvvdf, zx_tmp_fi3d)
871       IF (ok_orodr) THEN
872IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_oro(1:klon,1:klev)/pdtphys
873      CALL histwrite_phy(o_duoro, zx_tmp_fi3d)
874IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_oro(1:klon,1:klev)/pdtphys
875      CALL histwrite_phy(o_dvoro, zx_tmp_fi3d)
876IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_oro(1:klon,1:klev)/pdtphys
877      CALL histwrite_phy(o_dtoro, zx_tmp_fi3d)
878       ENDIF
879        IF (ok_orolf) THEN
880IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_lif(1:klon,1:klev)/pdtphys
881      CALL histwrite_phy(o_dulif, zx_tmp_fi3d)
882       ENDIF
883IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_lif(1:klon,1:klev)/pdtphys
884      CALL histwrite_phy(o_dvlif, zx_tmp_fi3d)
885
886IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lif(1:klon,1:klev)/pdtphys
887      CALL histwrite_phy(o_dtlif, zx_tmp_fi3d)
888
889       IF (ok_hines) THEN
890IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_hin(1:klon,1:klev)/pdtphys
891      CALL histwrite_phy(o_duhin, zx_tmp_fi3d)
892IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_hin(1:klon,1:klev)/pdtphys
893      CALL histwrite_phy(o_dvhin, zx_tmp_fi3d)
894IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_hin(1:klon,1:klev)/pdtphys
895      CALL histwrite_phy(o_dthin, zx_tmp_fi3d)
896        ENDIF
897      CALL histwrite_phy(o_rsu, swup)
898      CALL histwrite_phy(o_rsd, swdn)
899      CALL histwrite_phy(o_rlu, lwup)
900      CALL histwrite_phy(o_rld, lwdn)
901      CALL histwrite_phy(o_rsucs, swup0)
902      CALL histwrite_phy(o_rsdcs, swdn0)
903      CALL histwrite_phy(o_rlucs, lwup0)
904      CALL histwrite_phy(o_rldcs, lwdn0)
905IF(vars_defined) THEN
906      zx_tmp_fi3d(1:klon,1:klev)=d_t(1:klon,1:klev)+ &
907      d_t_dyn(1:klon,1:klev)
908ENDIF
909      CALL histwrite_phy(o_tnt, zx_tmp_fi3d)
910IF(vars_defined) THEN
911      zx_tmp_fi3d(1:klon,1:klev)=heat(1:klon,1:klev)/RDAY - &
912      cool(1:klon,1:klev)/RDAY
913ENDIF
914      CALL histwrite_phy(o_tntr, zx_tmp_fi3d)
915IF(vars_defined) THEN
916      zx_tmp_fi3d(1:klon,1:klev)= (d_t_lsc(1:klon,1:klev)+ &
917                                   d_t_eva(1:klon,1:klev)+ &
918                                   d_t_vdf(1:klon,1:klev))/pdtphys
919ENDIF
920      CALL histwrite_phy(o_tntscpbl, zx_tmp_fi3d)
921IF(vars_defined) THEN
922      zx_tmp_fi3d(1:klon,1:klev)=d_qx(1:klon,1:klev,ivap)+ &
923      d_q_dyn(1:klon,1:klev)
924ENDIF
925      CALL histwrite_phy(o_tnhus, zx_tmp_fi3d)
926IF(vars_defined) THEN
927      zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys+ &
928                                 d_q_eva(1:klon,1:klev)/pdtphys
929ENDIF
930      CALL histwrite_phy(o_tnhusscpbl, zx_tmp_fi3d)
931      CALL histwrite_phy(o_evu, coefm(:,:,is_ave))
932IF(vars_defined) THEN
933      zx_tmp_fi3d(1:klon,1:klev)=q_seri(1:klon,1:klev)+ &
934                                 ql_seri(1:klon,1:klev)
935ENDIF
936      CALL histwrite_phy(o_h2o, zx_tmp_fi3d)
937       if (iflag_con >= 3) then
938IF(vars_defined) THEN
939             zx_tmp_fi3d(1:klon,1:klev)=-1 * (dnwd(1:klon,1:klev)+ &
940                  dnwd0(1:klon,1:klev))
941ENDIF
942      CALL histwrite_phy(o_mcd, zx_tmp_fi3d)
943IF(vars_defined) THEN
944             zx_tmp_fi3d(1:klon,1:klev)=upwd(1:klon,1:klev) + &
945                  dnwd(1:klon,1:klev)+ dnwd0(1:klon,1:klev)
946ENDIF
947      CALL histwrite_phy(o_dmc, zx_tmp_fi3d)
948       else if (iflag_con == 2) then
949      CALL histwrite_phy(o_mcd,  pmfd)
950      CALL histwrite_phy(o_dmc,  pmfu + pmfd)
951       end if
952      CALL histwrite_phy(o_ref_liq, ref_liq)
953      CALL histwrite_phy(o_ref_ice, ref_ice)
954      if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. &
955       RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR. &
956       RCFC12_per.NE.RCFC12_act) THEN
957IF(vars_defined) zx_tmp_fi2d(1 : klon) = swupp ( 1 : klon, klevp1 )
958      CALL histwrite_phy(o_rsut4co2, zx_tmp_fi2d)
959IF(vars_defined) zx_tmp_fi2d(1 : klon) = lwupp ( 1 : klon, klevp1 )
960      CALL histwrite_phy(o_rlut4co2, zx_tmp_fi2d)
961IF(vars_defined) zx_tmp_fi2d(1 : klon) = swup0p ( 1 : klon, klevp1 )
962      CALL histwrite_phy(o_rsutcs4co2, zx_tmp_fi2d)
963IF(vars_defined) zx_tmp_fi2d(1 : klon) = lwup0p ( 1 : klon, klevp1 )
964      CALL histwrite_phy(o_rlutcs4co2, zx_tmp_fi2d)
965      CALL histwrite_phy(o_rsu4co2, swupp)
966      CALL histwrite_phy(o_rlu4co2, lwupp)
967      CALL histwrite_phy(o_rsucs4co2, swup0p)
968      CALL histwrite_phy(o_rlucs4co2, lwup0p)
969      CALL histwrite_phy(o_rsd4co2, swdnp)
970      CALL histwrite_phy(o_rld4co2, lwdnp)
971      CALL histwrite_phy(o_rsdcs4co2, swdn0p)
972      CALL histwrite_phy(o_rldcs4co2, lwdn0p)
973      ENDIF
974!!!!!!!!!!!! Sorties niveaux de pression NMC !!!!!!!!!!!!!!!!!!!!
975DO iff=7, nfiles
976
977      CALL histwrite_phy(o_tnondef,tnondef(:,:,iff-6),iff)
978      CALL histwrite_phy(o_ta,twriteSTD(:,:,iff-6),iff)
979      CALL histwrite_phy(o_zg,phiwriteSTD(:,:,iff-6),iff)
980      CALL histwrite_phy(o_hus,qwriteSTD(:,:,iff-6),iff)
981      CALL histwrite_phy(o_hur,rhwriteSTD(:,:,iff-6),iff)
982      CALL histwrite_phy(o_ua,uwriteSTD(:,:,iff-6),iff)
983      CALL histwrite_phy(o_va,vwriteSTD(:,:,iff-6),iff)
984      CALL histwrite_phy(o_wap,wwriteSTD(:,:,iff-6),iff)
985IF(vars_defined) THEN
986       DO k=1, nlevSTD
987        DO i=1, klon
988         IF(tnondef(i,k,iff-6).NE.missing_val) THEN
989          zx_tmp_fi3d(i,k) = (100.*tnondef(i,k,iff-6))/freq_moyNMC(iff-6)
990         ELSE
991          zx_tmp_fi3d(i,k) = missing_val
992         ENDIF
993        ENDDO
994      ENDDO
995ENDIF
996      CALL histwrite_phy(o_psbg,zx_tmp_fi3d,iff)
997IF(vars_defined) THEN
998       DO k=1, nlevSTD
999        DO i=1, klon
1000         IF(O3sumSTD(i,k,iff-6).NE.missing_val) THEN
1001          zx_tmp_fi3d(i,k) = O3sumSTD(i,k,iff-6) * 1.e+9
1002         ELSE
1003          zx_tmp_fi3d(i,k) = missing_val
1004         ENDIF
1005        ENDDO
1006       ENDDO !k=1, nlevSTD
1007ENDIF
1008      CALL histwrite_phy(o_tro3,zx_tmp_fi3d,iff)
1009       if (read_climoz == 2) THEN
1010IF(vars_defined) THEN
1011       DO k=1, nlevSTD
1012        DO i=1, klon
1013         IF(O3daysumSTD(i,k,iff-6).NE.missing_val) THEN
1014          zx_tmp_fi3d(i,k) = O3daysumSTD(i,k,iff-6) * 1.e+9
1015         ELSE
1016          zx_tmp_fi3d(i,k) = missing_val
1017         ENDIF
1018        ENDDO
1019       ENDDO !k=1, nlevSTD
1020ENDIF
1021      CALL histwrite_phy(o_tro3_daylight,zx_tmp_fi3d,iff)
1022      endif
1023      CALL histwrite_phy(o_uxv,uvsumSTD(:,:,iff-6),iff)
1024      CALL histwrite_phy(o_vxq,vqsumSTD(:,:,iff-6),iff)
1025      CALL histwrite_phy(o_vxT,vTsumSTD(:,:,iff-6),iff)
1026      CALL histwrite_phy(o_wxq,wqsumSTD(:,:,iff-6),iff)
1027      CALL histwrite_phy(o_vxphi,vphisumSTD(:,:,iff-6),iff)
1028      CALL histwrite_phy(o_wxT,wTsumSTD(:,:,iff-6),iff)
1029      CALL histwrite_phy(o_uxu,u2sumSTD(:,:,iff-6),iff)
1030      CALL histwrite_phy(o_vxv,v2sumSTD(:,:,iff-6),iff)
1031      CALL histwrite_phy(o_TxT,T2sumSTD(:,:,iff-6),iff)
1032ENDDO !nfiles
1033!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1034        IF (nqtot.GE.3) THEN
1035         DO iq=3,nqtot
1036             CALL histwrite_phy(o_trac(iq-2), qx(:,:,iq))
1037             CALL histwrite_phy(o_dtr_vdf(iq-2),d_tr_cl(:,:,iq-2))
1038             CALL histwrite_phy(o_dtr_the(iq-2),d_tr_th(:,:,iq-2))
1039             CALL histwrite_phy(o_dtr_con(iq-2),d_tr_cv(:,:,iq-2))
1040             CALL histwrite_phy(o_dtr_lessi_impa(iq-2),d_tr_lessi_impa(:,:,iq-2))
1041             CALL histwrite_phy(o_dtr_lessi_nucl(iq-2),d_tr_lessi_nucl(:,:,iq-2))
1042             CALL histwrite_phy(o_dtr_insc(iq-2),d_tr_insc(:,:,iq-2))
1043             CALL histwrite_phy(o_dtr_bcscav(iq-2),d_tr_bcscav(:,:,iq-2))
1044             CALL histwrite_phy(o_dtr_evapls(iq-2),d_tr_evapls(:,:,iq-2))
1045             CALL histwrite_phy(o_dtr_ls(iq-2),d_tr_ls(:,:,iq-2))
1046             CALL histwrite_phy(o_dtr_trsp(iq-2),d_tr_trsp(:,:,iq-2))
1047             CALL histwrite_phy(o_dtr_sscav(iq-2),d_tr_sscav(:,:,iq-2))
1048             CALL histwrite_phy(o_dtr_sat(iq-2),d_tr_sat(:,:,iq-2))
1049             CALL histwrite_phy(o_dtr_uscav(iq-2),d_tr_uscav(:,:,iq-2))
1050         zx_tmp_fi2d=0.
1051IF(vars_defined) THEN
1052         DO k=1,klev
1053            zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*qx(:,k,iq)
1054         ENDDO
1055ENDIF
1056            CALL histwrite_phy(o_trac_cum(iq-2), zx_tmp_fi2d)
1057         ENDDO
1058        ENDIF
1059
1060
1061        IF(.NOT.vars_defined) THEN
1062!$OMP MASTER
1063#ifndef CPP_NO_IOIPSL
1064            DO iff=1,nfiles
1065                IF (clef_files(iff)) THEN
1066                  CALL histend(nid_files(iff))
1067                  ndex2d = 0
1068                  ndex3d = 0
1069
1070                ENDIF ! clef_files
1071            ENDDO !  iff
1072#endif
1073#ifdef CPP_XIOS
1074            !On finalise l'initialisation:
1075            CALL wxios_closedef()
1076#endif
1077
1078!$OMP END MASTER
1079!$OMP BARRIER
1080            vars_defined = .TRUE.
1081
1082
1083        END IF
1084
1085    END DO
1086
1087    IF(vars_defined) THEN
1088! On synchronise les fichiers pour IOIPSL
1089#ifndef CPP_NO_IOIPSL
1090!$OMP MASTER
1091      DO iff=1,nfiles
1092          IF (ok_sync .AND. clef_files(iff)) THEN
1093              CALL histsync(nid_files(iff))
1094          ENDIF
1095      END DO
1096!$OMP END MASTER
1097#endif
1098    ENDIF
1099
1100     
1101
1102
1103    END SUBROUTINE phys_output_write
1104
1105
1106
1107  END MODULE phys_output_write_mod
1108
Note: See TracBrowser for help on using the repository browser.