source: LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90 @ 2002

Last change on this file since 2002 was 2002, checked in by Ehouarn Millour, 10 years ago

Further cleanup concerning XIOS (mainly about axes being defined as axes and not as groups of axes).
EM

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