source: LMDZ5/branches/LMDZ6_rc0/libf/phylmd/phys_output_write_mod.F90 @ 3839

Last change on this file since 3839 was 2381, checked in by acozic, 9 years ago

Make some commit to fit with INCA coupling

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