source: LMDZ6/branches/contrails/libf/phylmd/phys_output_write_mod.F90 @ 5589

Last change on this file since 5589 was 5589, checked in by aborella, 2 months ago

Multiple changes:

  • added new radiative diagnostics for contrails
  • added ok_rad_contrail option to allow for a double call of RRTM (w/ and w/o contrails)
  • transformed resuspension of snow into ice sedimentation (poprecip)
  • some modifications in poprecip in line with the ones from EV
  • cleaned sublimation of ice clouds in lmdz_lscp_condensation, option ok_ice_supersat
  • aviation emissions can now be read with IOIPSL (in lon/lat mode)
  • 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: 124.6 KB
Line 
1!
2! $Id: phys_output_write_mod.F90 5589 2025-03-26 17:05:40Z aborella $
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, flux_tr_wet, flux_tr_dry
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 (lors 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, ok_volcan, ivap, iliq, isol, ibs, ok_sync, &
20       ptconv, read_climoz, clevSTD, ptconvth, &
21       d_u, d_t, qx, d_qx, zmasse, flag_aerosol, flag_aerosol_strat, ok_cdnc, t, u1, v1)
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 infotrac_phy, ONLY: nbtr, nqtot, nqo, type_trac, tracers, niso, ntiso
28    USE strings_mod,  ONLY: maxlen
29    USE mod_phys_lmdz_para, ONLY: is_north_pole_phy,is_south_pole_phy
30    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
31    USE time_phylmdz_mod, ONLY: day_step_phy, start_time, itau_phy
32    USE vertical_layers_mod, ONLY : ap, bp, aps, bps
33    USE phystokenc_mod, ONLY: offline
34    USE phys_output_ctrlout_mod, ONLY: o_phis, o_aire, is_ter, is_lic, is_oce, &
35         o_longitude, o_latitude, &
36         o_Ahyb, o_Bhyb,o_Ahyb_bounds, o_Bhyb_bounds, &
37         o_Ahyb_mid, o_Bhyb_mid,o_Ahyb_mid_bounds, o_Bhyb_mid_bounds, &
38         is_ave, is_sic, o_contfracATM, o_contfracOR, &
39         o_aireTER, o_flat, o_slp, o_ptstar, o_pt0, o_tsol, &
40         o_t2m, o_t2m_min, o_t2m_max, &
41         o_t2m_min_mon, o_t2m_max_mon, &
42         o_nt2mout, o_nt2moutfg, &
43         o_nq2mout, o_nq2moutfg, &
44         o_nu2mout, o_nu2moutfg, &
45         o_q2m, o_ustar, o_u10m, o_v10m, &
46         o_wind10m, o_wind10max, o_wind100m, o_gusts, o_sicf, &
47         o_loadfactor_wind_onshore, o_loadfactor_wind_offshore, &
48         o_psol, o_mass, o_qsurf, o_qsol, &
49         o_precip, o_rain_fall, o_rain_con, o_ndayrain, o_plul, o_pluc, o_plun, &
50         o_snow, o_msnow, o_fsnow, o_evap, o_snowerosion, o_ustart_lic, o_qsalt_lic, o_rhosnow_lic, o_bsfall, &
51         o_ep,o_epmax_diag, & ! epmax_cape
52         o_tops, o_tops0, o_topl, o_topl0, &
53         o_SWupTOA, o_SWupTOAclr, o_SWupTOAcleanclr, o_SWdnTOA, o_fdiffSWdnSFC, &
54         o_SWdnTOAclr, o_nettop, o_SWup200, &
55         o_SWup200clr, o_SWdn200, o_SWdn200clr, &
56         o_LWupTOA, o_LWupTOAclr, &
57         o_LWup200, o_LWup200clr, o_LWdn200, &
58         o_LWdn200clr, o_sols, o_sols0, &
59         o_soll, o_radsol, o_soll0, o_SWupSFC, &
60         o_SWupSFCclr, o_SWupSFCcleanclr, o_SWdnSFC, o_SWdnSFCclr, o_SWdnSFCcleanclr, &
61         o_LWupSFC, o_LWdnSFC, o_LWupSFCclr, &
62         o_LWdnSFCclr, o_LWupTOAcleanclr, o_LWdnSFCcleanclr, o_bils, o_bils_diss, &
63         o_bils_ec,o_bils_ech, o_bils_tke, o_bils_kinetic, &
64         o_bils_latent, o_bils_enthalp, o_sens, &
65         o_fder, o_ffonte, o_fqcalving, o_fqfonte, o_mrroli, o_runofflic, &
66         o_taux, o_tauy, o_snowsrf, o_qsnow, &
67! SN runoff_diag
68         o_snowhgt, o_toice, o_sissnow, o_runoff, o_runoff_diag, &
69         o_albslw3, o_pourc_srf, o_fract_srf, &
70         o_taux_srf, o_tauy_srf, o_tsol_srf, &
71         o_evappot_srf, o_ustar_srf, o_u10m_srf, &
72         o_v10m_srf, o_t2m_srf, o_evap_srf, &
73         o_sens_srf, o_lat_srf, o_flw_srf, &
74         o_fsw_srf, o_wbils_srf, o_wbilo_srf, &
75         o_wevap_srf, o_wrain_srf, o_wsnow_srf, &
76         o_tke_srf, o_tke_max_srf,o_dltpbltke_srf, o_wstar, &
77         o_l_mixmin,o_l_mix, &
78         o_cdrm, o_cdrh, o_cldl, o_cldm, o_cldh, &
79         o_cldt, o_JrNt, o_cldljn, o_cldmjn, &
80         o_cldhjn, o_cldtjn, o_cldq, o_lwp, o_iwp, &
81         o_ue, o_ve, o_uq, o_vq, o_cape, o_pbase, &
82         o_uwat, o_vwat, &
83         o_ptop, o_fbase, o_plcl, o_plfc, &
84         o_wbeff, o_convoccur, o_cape_max, o_upwd, o_ep,o_epmax_diag, &
85         o_Mipsh, o_Ma, &
86         o_dnwd, o_dnwd0, o_ftime_deepcv, o_ftime_con, o_mc, &
87         o_prw, o_prlw, o_prsw, o_prbsw, o_water_budget, o_s_pblh, o_s_pblt, o_s_lcl, &
88         o_s_therm, o_uSTDlevs, o_vSTDlevs, &
89         o_wSTDlevs, o_zSTDlevs, o_qSTDlevs, &
90         o_tSTDlevs, epsfra, o_t_oce_sic, &
91         o_ale_bl, o_alp_bl, o_ale_wk, o_alp_wk, &
92         o_dtvdf_x    , o_dtvdf_w    , o_dqvdf_x    , o_dqvdf_w    , &
93         o_sens_x     , o_sens_w     , o_flat_x     , o_flat_w     , &
94         o_delta_tsurf, o_delta_tsurf_srf, &
95         o_cdragh_x   , o_cdragh_w   , o_cdragm_x   , o_cdragm_w   , &
96         o_kh         , o_kh_x       , o_kh_w       , &
97         o_ale, o_alp, o_cin, o_WAPE, o_wake_h, o_cv_gen, o_wake_dens, &
98         o_wake_s, o_wake_deltat, o_wake_deltaq, &
99         o_wake_omg, o_dtwak, o_dqwak, o_dqwak2d, o_Vprecip, &
100         o_qtaa, o_Clwaa, &
101         o_ftd, o_fqd, o_wdtrainA, o_wdtrainS, o_wdtrainM, &
102         o_n2, o_s2, o_strig, o_zcong, o_zlcl_th, o_proba_notrig, &
103         o_random_notrig, o_ale_bl_stat, &
104         o_ale_bl_trig, o_alp_bl_det, &
105         o_alp_bl_fluct_m, o_alp_bl_fluct_tke, &
106         o_alp_bl_conv, o_alp_bl_stat, &
107         o_slab_qflux, o_tslab, o_slab_bils, &
108         o_slab_bilg, o_slab_sic, o_slab_tice, &
109         o_slab_hdiff, o_slab_ekman, o_slab_gm,  &
110         o_weakinv, o_dthmin, o_cldtau, &
111         o_cldemi, o_pr_con_l, o_pr_con_i, &
112         o_pr_lsc_l, o_pr_lsc_i, o_pr_bs, o_re, o_fl, &
113         o_rh2m, &
114         o_qsat2m, o_tpot, o_tpote, o_SWnetOR, &
115         o_LWdownOR, o_snowl, &
116         o_solldown, o_dtsvdfo, o_dtsvdft, &
117         o_dtsvdfg, o_dtsvdfi, o_z0m, o_z0h,  o_od443aer, o_od550aer, &
118         o_dryod550aer, o_od865aer, o_abs550aer, o_od550lt1aer, &
119         o_sconcso4, o_sconcno3, o_sconcoa, o_sconcbc, &
120         o_sconcss, o_sconcdust, o_concso4, o_concno3, &
121         o_concoa, o_concbc, o_concss, o_concdust, &
122         o_loadso4, o_loadoa, o_loadbc, o_loadss, &
123         o_loaddust, o_loadno3, o_tausumaero, &
124         o_drytausumaero, o_tausumaero_lw, &
125         o_topswad, o_topswad0, o_solswad, o_solswad0, &
126         o_toplwad, o_toplwad0, o_sollwad, o_sollwad0, &
127         o_swtoaas_nat, o_swsrfas_nat, &
128         o_swtoacs_nat, o_swtoaas_ant, &
129         o_swsrfas_ant, o_swtoacs_ant, &
130         o_swsrfcs_ant, o_swtoacf_nat, &
131         o_swsrfcf_nat, o_swtoacf_ant, &
132         o_swsrfcs_nat, o_swsrfcf_ant, &
133         o_swtoacf_zero, o_swsrfcf_zero, &
134         o_topswai, o_solswai, o_toplwai, o_sollwai, o_scdnc, &
135         o_cldncl, o_reffclws, o_reffclwc, o_solbnd, o_stratomask,&
136         o_cldnvi, o_lcc, o_lcc3d, o_lcc3dcon, &
137         o_lcc3dstra, o_icc3dcon, o_icc3dstra, &
138         o_cldicemxrat, o_cldwatmxrat, o_reffclwtop, o_ec550aer, &
139         o_lwcon, o_iwcon, o_temp, o_theta, &
140         o_ovapinit, o_ovap, o_oliq, o_ocond, o_oice, o_geop,o_qbs, &
141         o_vitu, o_vitv, o_vitw, o_pres, o_paprs, &
142         o_zfull, o_zhalf, o_rneb, o_rnebjn, o_rnebcon, &
143         o_rnebls, o_rneblsvol, o_rhum, o_rhl, o_rhi, o_ozone, o_ozone_light, &
144         o_pfraclr, o_pfracld, o_cldfraliq, o_sigma2_icefracturb, o_mean_icefracturb,  &
145         o_qrainlsc, o_qsnowlsc, o_dqreva, o_dqrauto, o_dqrcol, o_dqrmelt, o_dqrfreez, &
146         o_dqssub, o_dqsauto, o_dqsagg, o_dqsrim, o_dqsmelt, o_dqsfreez, &
147         o_dqised, o_dcfsed, o_dqvcsed, &
148         o_duphy, o_dtphy, o_dqphy, o_dqphy2d, o_dqlphy, o_dqlphy2d, &
149         o_dqsphy, o_dqsphy2d, o_dqbsphy, o_dqbsphy2d, o_albe_srf, o_z0m_srf, o_z0h_srf, &
150         o_ages_srf, o_snow_srf, o_alb1, o_alb2, o_tke, o_tke_dissip, &
151         o_tke_max, o_kz, o_kz_max, o_clwcon, o_tke_shear, o_tke_buoy, o_tke_trans,  &
152         o_dtdyn, o_dqdyn, o_dqdyn2d, o_dqldyn, o_dqldyn2d, &
153         o_dqsdyn, o_dqsdyn2d, o_dqbsdyn, o_dqbsdyn2d, o_dudyn, o_dvdyn, &
154         o_dtcon, o_tntc, o_ducon, o_dvcon, &
155         o_dqcon, o_dqcon2d, o_tnhusc, o_tnhusc, o_dtlsc, &
156         o_dtlschr, o_dqlsc, o_dqlsc2d, o_beta_prec, &
157         o_dtlscth, o_dtlscst, o_dqlscth, o_dqlscth2d, &
158         o_dqlscst, o_dqlscst2d, o_plulth, o_plulst, &
159         o_ptconvth, o_lmaxth, o_dtvdf, &
160         o_dtdis, o_dqvdf, o_dqvdf2d, o_dteva, o_dqeva, o_dqeva2d, &
161         o_dqbsvdf, o_dtbs, o_dqbs, o_dqbsbs, &
162         o_ptconv, o_ratqs, o_dtthe, &
163         o_duthe, o_dvthe, o_ftime_th, &
164         o_f_th, o_e_th, o_w_th, o_q_th, &
165         o_a_th, o_cloudth_sth, o_cloudth_senv, &
166         o_cloudth_sigmath, o_cloudth_sigmaenv, &
167         o_d_th, o_f0_th, o_zmax_th, &
168         o_dqthe, o_dqthe2d, o_dtajs, o_dqajs, o_dqajs2d, o_dtswr, &
169         o_dtsw0, o_dtlwr, o_dtlw0, o_dtec, &
170         o_duvdf, o_dvvdf, o_duoro, o_dvoro, &
171         o_dtoro, o_dulif, o_dvlif, o_dtlif, &
172         o_du_gwd_hines, o_dv_gwd_hines, o_dthin, o_dqch4, o_rsu, &
173         o_du_gwd_front, o_dv_gwd_front, &
174         o_east_gwstress, o_west_gwstress, &
175         o_rsd, o_rlu, o_rld, o_rsucs, o_rsdcs, o_rsucsaf, o_rsdcsaf, &
176         o_rlucs, o_rldcs, o_tnt, o_tntr, &
177         o_tntscpbl, o_tnhus, o_tnhusscpbl, &
178         o_evu, o_h2o, o_mcd, o_dmc, o_ref_liq, &
179         o_ref_ice, o_rsut4co2, o_rlut4co2, &
180         o_rsutcs4co2, o_rlutcs4co2, o_rsu4co2, &
181         o_rlu4co2, o_rsucs4co2, o_rlucs4co2, &
182         o_rsd4co2, o_rld4co2, o_rsdcs4co2, &
183         o_rldcs4co2, o_tnondef, o_ta, o_zg, &
184         o_hus, o_hur, o_ua, o_va, o_wap, &
185         o_psbg, o_tro3, o_tro3_daylight, &
186         o_uxv, o_vxq, o_vxT, o_wxq, o_vxphi, &
187         o_wxT, o_uxu, o_vxv, o_TxT, o_trac, &
188         o_dtr_vdf, o_dtr_the, o_dtr_con, &
189         o_dtr_lessi_impa, o_dtr_lessi_nucl, &
190         o_dtr_insc, o_dtr_bcscav, o_dtr_evapls, &
191         o_dtr_ls, o_dtr_trsp, o_dtr_sscav, o_dtr_dry, &
192         o_dtr_sat, o_dtr_uscav, o_dtr_wet_con, &
193         o_trac_cum, o_du_gwd_rando, o_dv_gwd_rando, &
194         o_ustr_gwd_hines,o_vstr_gwd_hines,o_ustr_gwd_rando,o_vstr_gwd_rando, &
195         o_ustr_gwd_front,o_vstr_gwd_front, &
196         o_sens_prec_liq_oce, o_sens_prec_liq_sic, &
197         o_sens_prec_sol_oce, o_sens_prec_sol_sic, &
198         o_lat_prec_liq_oce, o_lat_prec_liq_sic, &
199         o_lat_prec_sol_oce, o_lat_prec_sol_sic, &
200         o_sza, &
201! Marine
202         o_map_prop_hc, o_map_prop_hist, o_map_emis_hc, o_map_iwp_hc, &
203         o_map_deltaz_hc, o_map_pcld_hc, o_map_tcld_hc, &
204         o_map_emis_hist, o_map_iwp_hist, o_map_deltaz_hist, &
205         o_map_rad_hist, &
206         o_map_emis_Cb, o_map_pcld_Cb, o_map_tcld_Cb, &
207         o_map_emis_ThCi, o_map_pcld_ThCi, o_map_tcld_ThCi, &
208         o_map_emis_Anv, o_map_pcld_Anv, o_map_tcld_Anv, &
209         o_map_ntot, o_map_hc,o_map_hist,o_map_Cb,o_map_ThCi,o_map_Anv, &
210#ifdef ISO
211! Isotopes
212         o_xtprecip,o_xtplul,o_xtpluc,o_xtovap,o_xtoliq,o_xtcond, &
213         o_xtrunoff_diag, &
214         o_xtevap,o_dxtdyn,o_dxtldyn,o_dxtcon,o_dxtlsc,o_dxteva, &
215         o_dxtajs,o_dxtvdf,o_dxtthe, o_dxtch4, &
216         o_dxtprod_nucl,o_dxtcosmo,o_dxtdecroiss, &
217         o_xtevap_srf, &
218#endif
219! Tropopause
220         o_alt_tropo, &
221         o_p_tropopause, o_z_tropopause, o_t_tropopause,  &
222         o_col_O3_strato, o_col_O3_tropo,                 &
223!-- LSCP - condensation and ice supersaturation variables
224         o_cfseri, o_dcfdyn, o_rvcseri, o_drvcdyn, &
225         o_qsub, o_qissr, o_qcld, o_subfra, o_issrfra, o_gammacond, &
226         o_dcfsub, o_dcfcon, o_dcfmix, o_dqiadj, o_dqisub, o_dqicon, o_dqimix, &
227         o_dqvcadj, o_dqvcsub, o_dqvccon, o_dqvcmix, o_qsatl, o_qsati, &
228         o_issrfra100to150, o_issrfra150to200, o_issrfra200to250, &
229         o_issrfra250to300, o_issrfra300to400, o_issrfra400to500, &
230!-- LSCP - aviation variables
231         o_rcontseri, o_drcontdyn, o_dqavi, o_contfra, &
232         o_Tcritcont, o_qcritcont, o_potcontfraP, o_potcontfraNP, &
233         o_dcontfracir, o_dcfavi, o_dqiavi, o_dqvcavi, o_flight_dist, o_flight_h2o, &
234         o_cldfra_nocont, o_cldtau_nocont, o_cldemi_nocont, o_cldh_nocont, &
235         o_contcov, o_iwp_nocont, o_iwc_nocont, o_ref_ice_nocont, &
236         o_tops_nocont, o_topl_nocont, o_sols_nocont, o_soll_nocont, &
237!--interactive CO2
238         o_flx_co2_ocean, o_flx_co2_ocean_cor, &
239         o_flx_co2_land, o_flx_co2_land_cor, &
240         o_flx_co2_ff, o_flx_co2_bb, &
241         o_delta_sst, o_delta_sal, o_ds_ns, o_dt_ns, o_dter, o_dser, o_tkt, &
242         o_tks, o_taur, o_sss, &
243!FC
244         o_zxfluxt,o_zxfluxq
245
246#ifdef CPP_ECRAD
247    USE phys_output_ctrlout_mod, ONLY:  &
248         o_soll0_s2,o_soll_s2,o_sols0_s2,o_sols_s2, &
249         o_topl0_s2,o_topl_s2,o_tops0_s2,o_tops_s2, &
250         o_SWupTOA_s2,o_SWupTOAclr_s2,o_cloud_cover_sw, &
251         o_cloud_cover_sw_s2,o_SWdnTOA_s2,o_SWdnTOAclr_s2, &
252         o_LWupSFCclr_s2, o_LWdnSFCclr_s2, o_SWupSFC_s2, &
253         o_SWupSFCclr_s2, o_SWdnSFC_s2, o_SWdnSFCclr_s2, &
254         o_LWupSFC_s2, o_LWdnSFC_s2, o_rlu_s2, o_rld_s2, &
255         o_rlucs_s2, o_rldcs_s2, o_rsu_s2, o_rsd_s2, &
256         o_rsucs_s2, o_rsdcs_s2   
257#endif
258
259    USE infotrac_phy, ONLY: nbtr_bin
260    USE phys_output_ctrlout_mod, ONLY:  &
261         o_budg_3D_nucl, o_budg_3D_cond_evap, o_budg_3D_ocs_to_so2, o_budg_3D_so2_to_h2so4, &
262         o_budg_sed_part, o_R2SO4, o_OCS_lifetime, o_SO2_lifetime, &
263         o_budg_3D_backgr_ocs, o_budg_3D_backgr_so2, &
264         o_budg_dep_dry_ocs, o_budg_dep_wet_ocs, &
265         o_budg_dep_dry_so2, o_budg_dep_wet_so2, &
266         o_budg_dep_dry_h2so4, o_budg_dep_wet_h2so4, &
267         o_budg_dep_dry_part, o_budg_dep_wet_part, &
268         o_budg_emi_ocs, o_budg_emi_so2, o_budg_emi_h2so4, o_budg_emi_part, &
269         o_budg_ocs_to_so2, o_budg_so2_to_h2so4, o_budg_h2so4_to_part, &
270         o_surf_PM25_sulf, o_ext_strat_550, o_tau_strat_550, &
271         o_vsed_aer, o_tau_strat_1020, o_ext_strat_1020, o_f_r_wet, &
272         o_SAD_sulfate, o_reff_sulfate, o_sulfmmr, o_nd_mode, o_sulfmmr_mode
273
274    USE lmdz_lscp_ini, ONLY: ok_poprecip, ok_ice_sedim
275
276    USE phys_output_ctrlout_mod, ONLY: o_heat_volc, o_cool_volc !NL
277    USE phys_state_var_mod, ONLY: heat_volc, cool_volc !NL
278
279    USE phys_state_var_mod, ONLY: pctsrf, rain_fall, snow_fall, bs_fall,&
280         qsol, z0m, z0h, fevap, agesno, &
281         nday_rain, ndayrain_mth, rain_con, snow_con, &
282         topsw, toplw, toplw0, swup, swdn, solswfdiff, &
283         topsw0, swupc0, swdnc0, swup0, swdn0, SWup200, SWup200clr, &
284         SWdn200, SWdn200clr, LWup200, LWup200clr, &
285         LWdn200, LWdn200clr, solsw, solsw0, sollw, &
286         radsol, swradcorr, sollw0, sollwdown, sollw, gustiness, &
287         sollwdownclr, lwdnc0, lwdn0, ftsol, ustar, u10m, &
288         v10m, pbl_tke, wake_delta_pbl_TKE, &
289         delta_tsurf, &
290         wstar, cape, ema_pcb, ema_pct, &
291         ema_cbmf, Mipsh, Ma, fm_therm, ale_bl, alp_bl, ale, &
292         alp, cin, wake_pe, wake_dens, cv_gen, wake_s, wake_deltat, &
293         wake_deltaq, ftd, fqd, ale_bl_trig, albsol1, &
294         ale_wake, ale_bl_stat, &
295         rnebcon, wo, falb1, albsol2, coefh, clwcon0, &
296         ratqs, entr_therm, zqasc, detr_therm, f0, &
297         lwup, lwdn, lwupc0, lwup0, coefm, &
298         swupp, lwupp, swupc0p, swup0p, lwupc0p, lwup0p, swdnp, lwdnp, &
299         swdnc0p, swdn0p, lwdnc0p, lwdn0p, tnondef, O3sumSTD, uvsumSTD, &
300         vqsumSTD, vTsumSTD, O3daysumSTD, wqsumSTD, &
301         vphisumSTD, wTsumSTD, u2sumSTD, v2sumSTD, &
302         T2sumSTD, nlevSTD, du_gwd_rando, du_gwd_front, &
303         ulevSTD, vlevSTD, wlevSTD, philevSTD, qlevSTD, tlevSTD, &
304         rhlevSTD, O3STD, O3daySTD, uvSTD, vqSTD, vTSTD, wqSTD, vphiSTD, &
305         wTSTD, u2STD, v2STD, T2STD, missing_val_nf90, delta_sal, ds_ns, &
306#ifdef ISO
307         xtrain_con, xtsnow_con, xtrain_fall, xtsnow_fall, fxtevap, &
308#endif
309         dt_ns, delta_sst, dter, dser
310         
311! AI 08 2023 pour ECRAD 3Deffect
312#ifdef CPP_ECRAD
313    USE phys_state_var_mod, ONLY: &
314        sollw0_s2,sollw_s2,solsw0_s2,solsw_s2, &
315        toplw0_s2,toplw_s2,topsw0_s2,topsw_s2, &
316        toplw0_s2,toplw_s2,topsw0_s2,topsw_s2, &
317        swup0_s2,swup_s2,swdn_s2,swdn0_s2,sollwdownclr_s2, &
318        sollwdown_s2,lwdn0_s2,lwup_s2,lwdn_s2,lwup0_s2,lwdn0_s2
319    USE phys_output_var_mod, ONLY: cloud_cover_sw, &
320        cloud_cover_sw_s2
321#endif
322
323    USE phys_local_var_mod, ONLY: zxfluxlat, slp, ptstar, pt0, zxtsol, zt2m, &
324         zn2mout, t2m_min_mon, t2m_max_mon, evap, &
325         snowerosion, zxustartlic, zxrhoslic, zxqsaltlic, &
326         l_mixmin,l_mix, pbl_eps, tke_shear, tke_buoy, tke_trans, &
327         zu10m, zv10m, zq2m, zustar, zxqsurf, &
328         rain_lsc, rain_num, snow_lsc, bils, sens, fder, &
329         zxffonte, zxfqcalving, zxfqfonte, zxrunofflic, fluxu, &
330         fluxv, zxsnow, qsnow, snowhgt, to_ice, &
331! SN runoff_diag
332         sissnow, runoff, runoff_diag, albsol3_lic, evap_pot, &
333         t2m, fluxt, fluxlat, fsollw, fsolsw, &
334         wfbils, wfevap, &
335         cdragm, cdragh, cldl, cldm, &
336         cldh, cldt, JrNt,   & ! only output names: cldljn,cldmjn,cldhjn,cldtjn
337         cldq, flwp, fiwp, ue, ve, uq, vq, &
338         uwat, vwat, &
339         plcl, plfc, wbeff, convoccur, upwd, dnwd, dnwd0, prw, prlw, prsw, prbsw, water_budget, &
340         s_pblh, s_pblt, s_lcl, s_therm, uwriteSTD, &
341         vwriteSTD, wwriteSTD, phiwriteSTD, qwriteSTD, &
342         twriteSTD, alp_wake, &
343!!         dtvdf_x    ,dtvdf_w    ,dqvdf_x    ,dqvdf_w    , &
344         d_t_vdf_x    ,d_t_vdf_w    ,d_q_vdf_x    ,d_q_vdf_w    , &
345         sens_x     ,sens_w     ,zxfluxlat_x,zxfluxlat_w, &
346         cdragh_x   ,cdragh_w   ,cdragm_x   ,cdragm_w   , &
347         kh         ,kh_x       ,kh_w       , &
348         wake_h, &
349         wake_omg, d_t_wake, d_q_wake, Vprecip, qtaa, Clw, &
350         wdtrainA, wdtrainS, wdtrainM, n2, s2, strig, zcong, zlcl_th, proba_notrig, &
351         random_notrig, &
352         cf_seri, d_cf_dyn, rvc_seri, d_rvc_dyn, &
353         qsub, qissr, qcld, subfra, issrfra, gamma_cond, &
354         dcf_sub, dcf_con, dcf_mix, &
355         dqi_adj, dqi_sub, dqi_con, dqi_mix, &
356         dqvc_adj, dqvc_sub, dqvc_con, dqvc_mix, &
357         qsatliq, qsatice, &
358         issrfra100to150, issrfra150to200, issrfra200to250, &
359         issrfra250to300, issrfra300to400, issrfra400to500, &
360         rcont_seri, d_rcont_dyn, d_q_avi, contfra, &
361         Tcritcont, qcritcont, potcontfraP, potcontfraNP, &
362         dcontfra_cir, dcf_avi, dqi_avi, dqvc_avi, flight_dist, flight_h2o, &
363         cldfra_nocont, cldtau_nocont, cldemi_nocont, cldh_nocont, &
364         contcov, fiwp_nocont, fiwc_nocont, ref_ice_nocont, &
365         topsw_nocont, toplw_nocont, solsw_nocont, sollw_nocont, &
366         alp_bl_det, alp_bl_fluct_m, alp_bl_conv, &
367         alp_bl_stat, alp_bl_fluct_tke, slab_wfbils, &
368         weak_inversion, dthmin, cldtau, cldemi, &
369         pmflxr, pmflxs, prfl, psfl,bsfl, re, fl, rh2m, &
370         qsat2m, tpote, tpot, d_ts, od443aer, od550aer, dryod550aer, &
371         od865aer, abs550aer, od550lt1aer, sconcso4, sconcno3, &
372         sconcoa, sconcbc, sconcss, sconcdust, concso4, concno3, &
373         concoa, concbc, concss, concdust, loadso4, &
374         loadoa, loadbc, loadss, loaddust, loadno3, tausum_aero, drytausum_aero, &
375         topswad_aero, topswad0_aero, solswad_aero, &
376         solswad0_aero, topsw_aero, solsw_aero, &
377         topsw0_aero, solsw0_aero, topswcf_aero, &
378         solswcf_aero, topswai_aero, solswai_aero, &
379         toplwad_aero, toplwad0_aero, sollwad_aero, &
380         sollwad0_aero, toplwai_aero, sollwai_aero, &
381         stratomask,&
382         zfice, &
383         ec550aer, flwc, fiwc, t_seri, theta, q_seri, &
384         ql_seri, qs_seri, qbs_seri, tr_seri, qbs_seri,&
385         zphi, u_seri, v_seri, omega, cldfra, &
386         rneb, rnebjn, rneblsvol,  &
387         zx_rh, zx_rhl, zx_rhi, &
388         pfraclr, pfracld, cldfraliq, sigma2_icefracturb, mean_icefracturb, &
389         qraindiag, qsnowdiag, dqreva, dqssub, &
390         dqrauto,dqrcol,dqrmelt,dqrfreez, &
391         dqsauto,dqsagg,dqsrim,dqsmelt,dqsfreez, &
392         dqised, dcfsed, dqvcsed, &
393         d_t_dyn,  &
394         d_q_dyn,  d_ql_dyn, d_qs_dyn, d_qbs_dyn,  &
395         d_q_dyn2d,  d_ql_dyn2d, d_qs_dyn2d, d_qbs_dyn2d, &
396         d_u_dyn, d_v_dyn, d_t_con, d_t_ajsb, d_t_ajs, &
397         d_u_ajs, d_v_ajs, &
398         d_u_con, d_v_con, d_q_con, d_q_ajs, d_t_lsc, &
399         d_t_lwr,d_t_lw0,d_t_swr,d_t_sw0, &
400         d_t_eva, d_q_lsc, beta_prec, d_t_lscth, &
401         d_t_lscst, d_q_lscth, d_q_lscst, plul_th, &
402         plul_st, d_t_vdf, d_t_diss, d_q_vdf, d_q_eva, &
403         d_t_bsss, d_q_bsss, d_qbs_bsss, d_qbs_vdf, &
404         zw2, fraca, zmax_th, d_q_ajsb, d_t_ec, d_u_vdf, &
405         d_v_vdf, d_u_oro, d_v_oro, d_t_oro, d_u_lif, &
406         d_v_lif, d_t_lif, du_gwd_hines, dv_gwd_hines, d_t_hin, &
407         dv_gwd_rando, dv_gwd_front, &
408         east_gwstress, west_gwstress, &
409         d_q_ch4, pmfd, pmfu, ref_liq, ref_ice, rhwriteSTD, &
410#ifdef ISO
411        xtrain_lsc, xtsnow_lsc, xt_seri, xtl_seri,xts_seri,xtevap, &
412        d_xt_dyn,d_xtl_dyn,d_xt_con,d_xt_vdf,d_xt_ajsb, &
413        d_xt_lsc,d_xt_eva,d_xt_ch4, &
414        d_xt_ajs, d_xt_ajsb, &
415        d_xt_prod_nucl,d_xt_cosmo,d_xt_decroiss, &
416        xtrunoff_diag, &
417#endif
418         ep, epmax_diag, &  ! epmax_cape
419         p_tropopause, t_tropopause, z_tropopause, &
420         zxfluxt,zxfluxq, &
421! offline
422         da, mp, phi, wght_cvfd
423    USE phys_output_var_mod, ONLY: scdnc, cldncl, reffclwtop, lcc, reffclws, &
424         reffclwc, cldnvi, lcc3d, lcc3dcon, lcc3dstra, icc3dcon, icc3dstra
425   
426    USE phys_local_var_mod, ONLY:  &
427         budg_3D_nucl, budg_3D_cond_evap, budg_3D_ocs_to_so2, budg_3D_so2_to_h2so4, &
428         budg_sed_part, R2SO4, OCS_lifetime, SO2_lifetime, &
429         budg_3D_backgr_ocs, budg_3D_backgr_so2, &
430         budg_dep_dry_ocs, budg_dep_wet_ocs, &
431         budg_dep_dry_so2, budg_dep_wet_so2, &
432         budg_dep_dry_h2so4, budg_dep_wet_h2so4, &
433         budg_dep_dry_part, budg_dep_wet_part, &
434         budg_emi_ocs, budg_emi_so2, budg_emi_h2so4, budg_emi_part, &
435         budg_ocs_to_so2, budg_so2_to_h2so4, budg_h2so4_to_part, &
436         surf_PM25_sulf, tau_strat_550, tausum_strat, &
437         vsed_aer, tau_strat_1020, f_r_wet, &
438         SAD_sulfate, reff_sulfate, sulfmmr, nd_mode, sulfmmr_mode
439
440    USE carbon_cycle_mod, ONLY: fco2_ff, fco2_bb, fco2_land, fco2_ocean
441    USE carbon_cycle_mod, ONLY: fco2_ocean_cor, fco2_land_cor
442
443    USE phys_output_var_mod, ONLY: vars_defined, snow_o, zfra_o, bils_diss, &
444         bils_ec,bils_ech, bils_tke, bils_kinetic, bils_latent, bils_enthalp, &
445         itau_con, nfiles, clef_files, nid_files, dryaod_diag, &
446         zustr_gwd_hines, zvstr_gwd_hines,zustr_gwd_rando, zvstr_gwd_rando, &
447         zustr_gwd_front, zvstr_gwd_front, sza_o,    &
448         sens_prec_liq_o, sens_prec_sol_o, lat_prec_liq_o, lat_prec_sol_o, &
449         cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv, &
450! Marine
451         map_prop_hc, map_prop_hist, &
452         map_emis_hc,map_iwp_hc,map_deltaz_hc,&
453         map_pcld_hc,map_tcld_hc,&
454         map_emis_hist,map_iwp_hist,map_deltaz_hist,&
455         map_rad_hist,&
456         map_ntot,map_hc,map_hist,&
457         map_Cb,map_ThCi,map_Anv,&
458         map_emis_Cb,map_pcld_Cb,map_tcld_Cb,&
459         map_emis_ThCi,map_pcld_ThCi,map_tcld_ThCi,&
460         map_emis_Anv,map_pcld_Anv,map_tcld_Anv, &
461         alt_tropo, &
462!Ionela
463         ok_4xCO2atm, tkt, tks, taur, sss
464
465    USE ocean_slab_mod, ONLY: nslay, tslab, slab_bilg, tice, seaice, &
466        slab_ekman,slab_hdiff,slab_gm,dt_ekman, dt_hdiff, dt_gm, dt_qflux
467    USE pbl_surface_mod, ONLY: snow
468    USE indice_sol_mod, ONLY: nbsrf
469#ifdef ISO
470    USE isotopes_mod, ONLY: iso_HTO, isoName
471#endif
472    USE geometry_mod, ONLY: cell_area, latitude_deg, longitude_deg
473    USE surface_data, ONLY: type_ocean, version_ocean, ok_veget, landice_opt
474    USE aero_mod, ONLY: naero_tot, id_STRAT_phy
475    USE ioipsl, ONLY: histend, histsync
476    USE iophy, ONLY: set_itau_iophy, histwrite_phy
477    USE netcdf, ONLY: nf90_fill_real
478    USE print_control_mod, ONLY: prt_level,lunout
479    ! ug Pour les sorties XIOS
480    USE lmdz_xios
481    use wxios_mod, ONLY: wxios_closedef, missing_val_xios=>missing_val, wxios_set_context
482    USE phys_cal_mod, ONLY : mth_len
483
484#ifdef CPP_RRTM
485    USE YOESW, ONLY : RSUN
486#endif
487USE compbl_mod_h
488    USE alpale_mod
489        USE clesphys_mod_h
490    USE tracinca_mod, ONLY: config_inca
491    USE config_ocean_skin_m, ONLY: activate_ocean_skin
492
493    USE vertical_layers_mod, ONLY: presnivs
494    USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_STRATAER
495
496    USE yomcst_mod_h
497    USE phys_constants_mod, ONLY: dobson_u
498IMPLICIT NONE
499
500
501
502    ! Input
503    INTEGER :: itap, ivap, iliq, isol, ibs, read_climoz
504    INTEGER, DIMENSION(klon) :: lmax_th
505    LOGICAL :: aerosol_couple, ok_sync
506    LOGICAL :: ok_ade, ok_aie, ok_volcan
507    LOGICAL, DIMENSION(klon, klev) :: ptconv, ptconvth
508    REAL :: pdtphys
509    CHARACTER (LEN=4), DIMENSION(nlevSTD) :: clevSTD
510    REAL, DIMENSION(klon,nlevSTD) :: zx_tmp_fi3d_STD
511    REAL, DIMENSION(klon) :: pphis
512    REAL, DIMENSION(klon, klev) :: pplay, d_u, d_t
513    REAL, DIMENSION(klon, klev+1) :: paprs
514    REAL, DIMENSION(klon,klev,nqtot) :: qx, d_qx
515    REAL, DIMENSION(klon, klev) :: zmasse
516    INTEGER :: flag_aerosol_strat
517    INTEGER :: flag_aerosol
518    LOGICAL :: ok_cdnc
519    REAL, DIMENSION(klon,klev) :: t   ! output for phystoken - offline flux
520    REAL, DIMENSION(klon) :: u1, v1   ! output for phystoken - offline flux
521   
522    REAL, DIMENSION(3) :: freq_moyNMC
523
524    ! Local
525    INTEGER :: itau_w
526    INTEGER :: i, iinit, iinitend=1, iff, iq, nsrf, k, ll, naero
527    REAL, DIMENSION (klon) :: zx_tmp_fi2d, zpt_conv2d, wind100m
528    REAL, DIMENSION (klon,klev) :: zx_tmp_fi3d, zpt_conv
529    REAL, DIMENSION (klon,klev+1) :: zx_tmp_fi3d1
530    REAL, DIMENSION (klon,NSW) :: zx_tmp_fi3dsp
531    CHARACTER (LEN=4)              :: bb2
532    INTEGER, DIMENSION(nbp_lon*nbp_lat)  :: ndex2d
533    INTEGER, DIMENSION(nbp_lon*nbp_lat*klev) :: ndex3d
534!   REAL, PARAMETER :: missing_val=nf90_fill_real
535    REAL, DIMENSION(klev+1,2) :: Ahyb_bounds, Bhyb_bounds
536    REAL, DIMENSION(klev,2) :: Ahyb_mid_bounds, Bhyb_mid_bounds
537    INTEGER :: ilev
538    INTEGER, SAVE :: kmax_100m
539!$OMP THREADPRIVATE(kmax_100m)
540    REAL :: x
541    REAL :: missing_val
542    REAL, PARAMETER :: un_jour=86400.
543    CHARACTER(len=12) :: nvar   
544    INTEGER :: ISW, itr, ixt, it
545    CHARACTER*1 ch1
546    CHARACTER(LEN=maxlen) :: varname, dn
547    REAL, DIMENSION(klon,klev) :: coefh_stok
548   
549    LOGICAL, PARAMETER :: debug_strataer=.FALSE.
550    CHARACTER(LEN=maxlen) :: unt
551
552#ifdef ISO
553    CHARACTER(LEN=maxlen) :: outiso
554#endif
555
556    REAL,DIMENSION(klon,klev) :: z, dz
557    REAL,DIMENSION(klon)      :: zrho, zt
558
559    ! On calcul le nouveau tau:
560    itau_w = itau_phy + itap
561    ! On le donne à iophy pour que les histwrite y aient accès:
562    CALL set_itau_iophy(itau_w)
563
564 !   IF (.NOT.vars_defined) THEN
565       iinitend = 1
566 !   ELSE
567 !      iinitend = 1
568 !   ENDIF
569
570    IF (using_xios) CALL wxios_set_context
571
572    IF (using_xios) THEN
573      missing_val=missing_val_xios
574    ELSE
575      missing_val=missing_val_nf90
576    ENDIF
577
578    IF (.NOT.vars_defined) THEN
579      kmax_100m=1
580      DO k=1, klev-1
581        IF (presnivs(k).GT.0.97*101325.) kmax_100m = k !--finding out max level for 100 m with a good margin
582      ENDDO
583    ENDIF
584
585    Ahyb_bounds(1,1) = 0.
586    Ahyb_bounds(1,2) = aps(1)
587    Bhyb_bounds(1,1) = 1.
588    Bhyb_bounds(1,2) = bps(1)   
589
590    DO ilev=2,klev
591      Ahyb_bounds(ilev,1) = aps(ilev-1)
592      Ahyb_bounds(ilev,2) = aps(ilev)
593      Bhyb_bounds(ilev,1) = bps(ilev-1)
594      Bhyb_bounds(ilev,2) = bps(ilev)
595    ENDDO
596
597    Ahyb_bounds(klev+1,1) = aps(klev)
598    Ahyb_bounds(klev+1,2) = 0.
599    Bhyb_bounds(klev+1,1) = bps(klev)
600    Bhyb_bounds(klev+1,2) = 0.
601
602    DO ilev=1, klev
603      Ahyb_mid_bounds(ilev,1) = ap(ilev)
604      Ahyb_mid_bounds(ilev,2) = ap(ilev+1)
605      Bhyb_mid_bounds(ilev,1) = bp(ilev)
606      Bhyb_mid_bounds(ilev,2) = bp(ilev+1)
607    ENDDO
608
609
610    ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
611    DO iinit=1, iinitend
612!      print *,'IFF iinit=', iinit, iinitend
613       IF (using_xios) THEN
614         !$OMP MASTER
615         IF (vars_defined) THEN
616            IF (prt_level >= 10) then
617               write(lunout,*)"phys_output_write: call xios_update_calendar, itau_w=",itau_w
618            ENDIF
619!            CALL xios_update_calendar(itau_w)
620            CALL xios_update_calendar(itap)
621         ENDIF
622         !$OMP END MASTER
623         !$OMP BARRIER
624       ENDIF
625
626       ! On procède à l'écriture ou à la définition des nombreuses variables:
627!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
628       CALL histwrite_phy(o_phis, pphis)
629
630       zx_tmp_fi2d = cell_area
631       IF (is_north_pole_phy) then
632         zx_tmp_fi2d(1) = cell_area(1)/nbp_lon
633       ENDIF
634       IF (is_south_pole_phy) then
635         zx_tmp_fi2d(klon) = cell_area(klon)/nbp_lon
636       ENDIf
637       CALL histwrite_phy(o_aire, zx_tmp_fi2d)
638
639       IF (vars_defined) THEN
640          DO i=1, klon
641             zx_tmp_fi2d(i)=pctsrf(i,is_ter)+pctsrf(i,is_lic)
642          ENDDO
643       ENDIF
644
645       CALL histwrite_phy(o_contfracATM, zx_tmp_fi2d)
646       CALL histwrite_phy(o_contfracOR, pctsrf(:,is_ter))
647!
648       IF (using_xios) THEN
649
650         CALL histwrite_phy("R_ecc",R_ecc)
651         CALL histwrite_phy("R_peri",R_peri)
652         CALL histwrite_phy("R_incl",R_incl)
653         CALL histwrite_phy("solaire",solaire)
654         CALL histwrite_phy(o_Ahyb, ap)
655         CALL histwrite_phy(o_Bhyb, bp)
656         CALL histwrite_phy(o_Ahyb_bounds, Ahyb_bounds)
657         CALL histwrite_phy(o_Bhyb_bounds, Bhyb_bounds)
658         CALL histwrite_phy(o_Ahyb_mid, aps)
659         CALL histwrite_phy(o_Bhyb_mid, bps)
660         CALL histwrite_phy(o_Ahyb_mid_bounds, Ahyb_mid_bounds)
661         CALL histwrite_phy(o_Bhyb_mid_bounds, Bhyb_mid_bounds)
662         CALL histwrite_phy(o_longitude, longitude_deg)
663         CALL histwrite_phy(o_latitude, latitude_deg)
664!
665#ifdef CPP_RRTM
666         IF (iflag_rrtm.EQ.1) THEN
667           DO ISW=1, NSW
668             WRITE(ch1,'(i1)') ISW
669  !          zx_tmp_0d=RSUN(ISW)
670  !          CALL histwrite_phy("rsun"//ch1,zx_tmp_0d)
671             CALL histwrite_phy("rsun"//ch1,RSUN(ISW))
672           ENDDO
673         ENDIF
674#endif
675!
676         CALL histwrite_phy("co2_ppm",co2_ppm)
677         CALL histwrite_phy("CH4_ppb",CH4_ppb)
678         CALL histwrite_phy("N2O_ppb",N2O_ppb)
679         CALL histwrite_phy("CFC11_ppt",CFC11_ppt)
680         CALL histwrite_phy("CFC12_ppt",CFC12_ppt)
681!
682       ENDIF !using_xios
683
684!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
685! Simulateur AIRS
686       IF (ok_airs) then
687         CALL histwrite_phy(o_alt_tropo,alt_tropo)
688 
689         CALL histwrite_phy(o_map_prop_hc,map_prop_hc)
690         CALL histwrite_phy(o_map_prop_hist,map_prop_hist)
691
692         CALL histwrite_phy(o_map_emis_hc,map_emis_hc)
693         CALL histwrite_phy(o_map_iwp_hc,map_iwp_hc)
694         CALL histwrite_phy(o_map_deltaz_hc,map_deltaz_hc)
695         CALL histwrite_phy(o_map_pcld_hc,map_pcld_hc)
696         CALL histwrite_phy(o_map_tcld_hc,map_tcld_hc)
697
698         CALL histwrite_phy(o_map_emis_hist,map_emis_hist)
699         CALL histwrite_phy(o_map_iwp_hist,map_iwp_hist)
700         CALL histwrite_phy(o_map_deltaz_hist,map_deltaz_hist)
701
702         CALL histwrite_phy(o_map_ntot,map_ntot)
703         CALL histwrite_phy(o_map_hc,map_hc)
704         CALL histwrite_phy(o_map_hist,map_hist)
705
706         CALL histwrite_phy(o_map_Cb,map_Cb)
707         CALL histwrite_phy(o_map_ThCi,map_ThCi)
708         CALL histwrite_phy(o_map_Anv,map_Anv)
709
710         CALL histwrite_phy(o_map_emis_Cb,map_emis_Cb)
711         CALL histwrite_phy(o_map_pcld_Cb,map_pcld_Cb)
712         CALL histwrite_phy(o_map_tcld_Cb,map_tcld_Cb)
713
714         CALL histwrite_phy(o_map_emis_ThCi,map_emis_ThCi)
715         CALL histwrite_phy(o_map_pcld_ThCi,map_pcld_ThCi)
716         CALL histwrite_phy(o_map_tcld_ThCi,map_tcld_ThCi)
717
718         CALL histwrite_phy(o_map_emis_Anv,map_emis_Anv)
719         CALL histwrite_phy(o_map_pcld_Anv,map_pcld_Anv)
720         CALL histwrite_phy(o_map_tcld_Anv,map_tcld_Anv)
721       ENDIF
722
723       CALL histwrite_phy(o_sza, sza_o)
724       CALL histwrite_phy(o_flat, zxfluxlat)
725       CALL histwrite_phy(o_ptstar, ptstar)
726       CALL histwrite_phy(o_pt0, pt0)
727       CALL histwrite_phy(o_slp, slp)
728       CALL histwrite_phy(o_tsol, zxtsol)
729       CALL histwrite_phy(o_t2m, zt2m)
730       CALL histwrite_phy(o_t2m_min, zt2m)
731       CALL histwrite_phy(o_t2m_max, zt2m)
732       CALL histwrite_phy(o_t2m_max_mon, t2m_max_mon)
733       CALL histwrite_phy(o_t2m_min_mon, t2m_min_mon)
734
735       IF (vars_defined) THEN
736          DO i=1, klon
737             zx_tmp_fi2d(i)=REAL(zn2mout(i,1))
738          ENDDO
739       ENDIF
740       CALL histwrite_phy(o_nt2mout, zx_tmp_fi2d)
741
742       IF (vars_defined) THEN
743          DO i=1, klon
744             zx_tmp_fi2d(i)=REAL(zn2mout(i,2))
745          ENDDO
746       ENDIF
747       CALL histwrite_phy(o_nt2moutfg, zx_tmp_fi2d)
748
749       IF (vars_defined) THEN
750          DO i=1, klon
751             zx_tmp_fi2d(i)=REAL(zn2mout(i,3))
752          ENDDO
753       ENDIF
754       CALL histwrite_phy(o_nq2mout, zx_tmp_fi2d)
755
756       IF (vars_defined) THEN
757          DO i=1, klon
758             zx_tmp_fi2d(i)=REAL(zn2mout(i,4))
759          ENDDO
760       ENDIF
761       CALL histwrite_phy(o_nq2moutfg, zx_tmp_fi2d)
762
763       IF (vars_defined) THEN
764          DO i=1, klon
765             zx_tmp_fi2d(i)=REAL(zn2mout(i,5))
766          ENDDO
767       ENDIF
768       CALL histwrite_phy(o_nu2mout, zx_tmp_fi2d)
769
770       IF (vars_defined) THEN
771          DO i=1, klon
772             zx_tmp_fi2d(i)=REAL(zn2mout(i,6))
773          ENDDO
774       ENDIF
775       CALL histwrite_phy(o_nu2moutfg, zx_tmp_fi2d)
776
777       IF (vars_defined) THEN
778          DO i=1, klon
779             zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
780          ENDDO
781       ENDIF
782       CALL histwrite_phy(o_wind10m, zx_tmp_fi2d)
783
784       IF (vars_defined) THEN
785          DO i=1, klon
786             zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
787          ENDDO
788       ENDIF
789       CALL histwrite_phy(o_wind10max, zx_tmp_fi2d)
790
791       CALL histwrite_phy(o_gusts, gustiness)
792
793       IF (vars_defined) THEN
794          DO k = 1, kmax_100m                                      !--we could stop much lower
795            zrho(:) = pplay(:,k)/t_seri(:,k)/RD                    ! air density in kg/m3
796            dz(:,k) = (paprs(:,k)-paprs(:,k+1))/zrho(:)/RG         ! layer thickness in m
797            IF (k==1) THEN
798              z(:,1) = (paprs(:,1)-pplay(:,1))/zrho(:)/RG          ! altitude middle of first layer in m
799              zt(:)  = dz(:,1)                                     ! altitude top of first layer in m
800            ELSE
801              z(:,k) = zt(:) + (paprs(:,k)-pplay(:,k))/zrho(:)/RG  ! altitude middle of layer k in m
802              zt(:)  = zt(:) + dz(:,k)                             ! altitude top of layer k in m
803            ENDIF
804          ENDDO
805          wind100m(:)=missing_val
806          DO k=1, kmax_100m-1                                      !--we could stop much lower
807            DO i=1,klon
808              IF (z(i,k).LT.100..AND.z(i,k+1).GE.100.) THEN
809                wind100m(i)=SQRT( (u_seri(i,k)+(100.-z(i,k))/(z(i,k+1)-z(i,k))*(u_seri(i,k+1)-u_seri(i,k)))**2.0 + &
810                                  (v_seri(i,k)+(100.-z(i,k))/(z(i,k+1)-z(i,k))*(v_seri(i,k+1)-v_seri(i,k)))**2.0 )
811              ENDIF
812            ENDDO
813          ENDDO
814       ENDIF
815       CALL histwrite_phy(o_wind100m, wind100m)
816
817       IF (vars_defined) THEN
818         !--polynomial fit for 14,Vestas,1074,V136/3450 kW windmill - Olivier
819         DO i=1,klon
820           IF (pctsrf(i,is_ter).GT.0.05 .AND. wind100m(i).NE.missing_val) THEN
821             x=wind100m(i)
822             IF (x.LE.3.0 .OR. x.GE.22.5) THEN
823               zx_tmp_fi2d(i)=0.0
824             ELSE IF (x.GE.10.0) THEN
825               zx_tmp_fi2d(i)=1.0
826             ELSE
827               zx_tmp_fi2d(i)= 10.73 + x*(-14.69 + x*(8.339 + x*(-2.59 + x*(0.4893 + x*(-0.05898 + x*(0.004627 + &
828                               x*(-0.0002352 + x*(7.478e-06 + x*(-1.351e-07 + x*(1.059e-09))))))))))
829               zx_tmp_fi2d(i)=MIN(MAX(zx_tmp_fi2d(i),0.0),1.0)
830             ENDIF
831           ELSE
832             zx_tmp_fi2d(i)=missing_val
833           ENDIF
834         ENDDO
835       ENDIF
836       CALL histwrite_phy(o_loadfactor_wind_onshore, zx_tmp_fi2d)
837
838       IF (vars_defined) THEN
839         !--polynomial fit for 14,Vestas,867,V164/8000 kW - Olivier
840         DO i=1,klon
841           IF (pctsrf(i,is_oce).GT.0.05 .AND. wind100m(i).NE.missing_val) THEN
842             x=wind100m(i)
843             IF (x.LE.3.0 .OR. x.GE.25.5) THEN
844               zx_tmp_fi2d(i)=0.0
845             ELSE IF (x.GE.12.5) THEN
846               zx_tmp_fi2d(i)=1.0
847             ELSE
848               zx_tmp_fi2d(i)= 20.59 + x*(-22.39 + x*(10.25 + x*(-2.601 + x*(0.4065 + x*(-0.04099 + x*(0.002716 + &
849                               x*(-0.0001175 + x*(3.195e-06 + x*(-4.959e-08 + x*(3.352e-10))))))))))
850               zx_tmp_fi2d(i)=MIN(MAX(zx_tmp_fi2d(i),0.0),1.0)
851             ENDIF
852           ELSE
853             zx_tmp_fi2d(i)=missing_val
854           ENDIF
855         ENDDO
856       ENDIF
857       CALL histwrite_phy(o_loadfactor_wind_offshore, zx_tmp_fi2d)
858
859       IF (vars_defined) THEN
860          DO i = 1, klon
861             zx_tmp_fi2d(i) = pctsrf(i,is_sic)
862          ENDDO
863       ENDIF
864       CALL histwrite_phy(o_sicf, zx_tmp_fi2d)
865       CALL histwrite_phy(o_q2m, zq2m)
866       !IF (vars_defined) zx_tmp_fi2d = zustar
867       !set ustar output variable as directly related to actual surface stress
868       IF (vars_defined) THEN
869          zx_tmp_fi2d=0.
870          DO nsrf=1,nbsrf
871             zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*((t_seri(:,1)*RD/pplay(:,1))**0.5)*(fluxu(:,1,nsrf)**2+fluxv(:,1,nsrf)**2)**0.25
872          ENDDO           
873       ENDIF
874       CALL histwrite_phy(o_ustar, zx_tmp_fi2d)
875       CALL histwrite_phy(o_u10m, zu10m)
876       CALL histwrite_phy(o_v10m, zv10m)
877
878       IF (vars_defined) THEN
879          DO i = 1, klon
880             zx_tmp_fi2d(i) = paprs(i,1)
881          ENDDO
882       ENDIF
883       CALL histwrite_phy(o_psol, zx_tmp_fi2d)
884       CALL histwrite_phy(o_mass, zmasse)
885       CALL histwrite_phy(o_qsurf, zxqsurf)
886
887       IF (.NOT. ok_veget) THEN
888          CALL histwrite_phy(o_qsol, qsol)
889       ENDIF
890
891       IF (vars_defined) THEN
892          IF (ok_bs) THEN
893             DO i = 1, klon
894             zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i) + bs_fall(i)
895             ENDDO
896          ELSE
897             DO i = 1, klon
898             zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)
899             ENDDO
900          ENDIF
901       ENDIF
902
903       CALL histwrite_phy(o_precip, zx_tmp_fi2d)
904       CALL histwrite_phy(o_rain_fall, rain_fall)
905       CALL histwrite_phy(o_ndayrain, ndayrain_mth)
906
907       ! epmax_cape:
908!       CALL histwrite_phy(o_epmax_diag, epmax_diag)
909       CALL histwrite_phy(o_ep, ep)
910
911       IF (vars_defined) THEN
912          DO i = 1, klon
913             zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)
914          ENDDO
915       ENDIF
916       CALL histwrite_phy(o_plul, zx_tmp_fi2d)
917       CALL histwrite_phy(o_plun, rain_num)
918
919       IF (vars_defined) THEN
920          DO i = 1, klon
921             zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)
922          ENDDO
923       ENDIF
924       CALL histwrite_phy(o_pluc, zx_tmp_fi2d)
925       CALL histwrite_phy(o_rain_con, rain_con)
926       CALL histwrite_phy(o_snow, snow_fall)
927       CALL histwrite_phy(o_msnow, zxsnow)
928       CALL histwrite_phy(o_fsnow, zfra_o)
929       CALL histwrite_phy(o_evap, evap)
930
931       IF (ok_bs) THEN
932           CALL histwrite_phy(o_bsfall, bs_fall)     
933           CALL histwrite_phy(o_snowerosion, snowerosion)
934           CALL histwrite_phy(o_ustart_lic, zxustartlic)
935           CALL histwrite_phy(o_rhosnow_lic, zxrhoslic)
936           CALL histwrite_phy(o_qsalt_lic, zxqsaltlic)
937       ENDIF
938
939       IF (vars_defined) THEN
940         zx_tmp_fi2d = topsw*swradcorr
941       ENDIF
942       CALL histwrite_phy(o_tops, zx_tmp_fi2d)
943
944       IF (vars_defined) THEN
945         zx_tmp_fi2d = topsw0*swradcorr
946       ENDIF
947       CALL histwrite_phy(o_tops0, zx_tmp_fi2d)
948
949       CALL histwrite_phy(o_topl, toplw)
950       CALL histwrite_phy(o_topl0, toplw0)
951
952! offline
953       IF (using_xios) THEN
954         IF (offline) THEN
955
956            coefh_stok(:,1)      = cdragh(:)
957            coefh_stok(:,2:klev) = coefh(:,2:klev, is_ave)
958         
959            CALL histwrite_phy('upwd_stok', upwd)
960            CALL histwrite_phy('t_stok', t)
961            CALL histwrite_phy('fm_th_stok', fm_therm(:,1:klev))
962            CALL histwrite_phy('en_th_stok', entr_therm)
963            CALL histwrite_phy('da_stok',da )
964            CALL histwrite_phy('mp_stok',mp )
965            CALL histwrite_phy('dnwd_stok', dnwd)
966            CALL histwrite_phy('wght_stok', wght_cvfd)
967            CALL histwrite_phy('coefh_stok', coefh_stok)
968            CALL histwrite_phy('yu1_stok', u1)
969            CALL histwrite_phy('yv1_stok', v1)
970
971            DO k=1,klev
972               IF (k<10) THEN
973                  WRITE(nvar,'(i1)') k
974               ELSE IF (k<100) THEN
975                  WRITE(nvar,'(i2)') k
976               ELSE
977                  WRITE(nvar,'(i3)') k
978               ENDIF
979               nvar='phi_lev'//trim(nvar)
980               CALL histwrite_phy(nvar,phi(:,:,k))
981            ENDDO
982         
983         ENDIF
984       ENDIF
985       
986       IF (vars_defined) THEN
987          zx_tmp_fi2d(:) = swup(:,klevp1)*swradcorr(:)
988       ENDIF
989       CALL histwrite_phy(o_SWupTOA, zx_tmp_fi2d)
990
991       IF (vars_defined) THEN
992          zx_tmp_fi2d(:) = swup0(:,klevp1)*swradcorr(:)
993       ENDIF
994       CALL histwrite_phy(o_SWupTOAclr, zx_tmp_fi2d)
995
996       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
997          IF (vars_defined) THEN
998             zx_tmp_fi2d(:) = swupc0(:,klevp1)*swradcorr(:)
999          ENDIF
1000          CALL histwrite_phy(o_SWupTOAcleanclr, zx_tmp_fi2d)
1001       ENDIF
1002
1003       IF (vars_defined) THEN
1004          zx_tmp_fi2d(:) = swdn(:,klevp1)*swradcorr(:)
1005       ENDIF
1006       CALL histwrite_phy(o_SWdnTOA, zx_tmp_fi2d)
1007
1008       IF (vars_defined) THEN
1009          zx_tmp_fi2d(:) = swdn0(:,klevp1)*swradcorr(:)
1010       ENDIF
1011       CALL histwrite_phy(o_SWdnTOAclr, zx_tmp_fi2d)
1012
1013       IF (vars_defined) THEN
1014          zx_tmp_fi2d(:) = topsw(:)*swradcorr(:)-toplw(:)
1015       ENDIF
1016       CALL histwrite_phy(o_nettop, zx_tmp_fi2d)
1017       
1018       IF (vars_defined) THEN
1019          zx_tmp_fi2d = SWup200*swradcorr
1020       ENDIF
1021       CALL histwrite_phy(o_SWup200, zx_tmp_fi2d)
1022       
1023       IF (vars_defined) THEN
1024          zx_tmp_fi2d = SWup200clr*swradcorr
1025       ENDIF
1026       CALL histwrite_phy(o_SWup200clr, zx_tmp_fi2d)
1027       
1028       IF (vars_defined) THEN
1029          zx_tmp_fi2d = SWdn200*swradcorr
1030       ENDIF
1031       CALL histwrite_phy(o_SWdn200, zx_tmp_fi2d)
1032       
1033       
1034       IF (vars_defined) THEN
1035          zx_tmp_fi2d = SWdn200clr*swradcorr
1036       ENDIF
1037       CALL histwrite_phy(o_SWdn200clr, zx_tmp_fi2d)
1038       
1039       CALL histwrite_phy(o_LWup200, LWup200)
1040       CALL histwrite_phy(o_LWup200clr, LWup200clr)
1041       CALL histwrite_phy(o_LWdn200, LWdn200)
1042       CALL histwrite_phy(o_LWdn200clr, LWdn200clr)
1043       
1044       IF (vars_defined) THEN
1045          zx_tmp_fi2d = solsw*swradcorr
1046       ENDIF
1047       CALL histwrite_phy(o_sols, zx_tmp_fi2d)
1048       
1049       IF (vars_defined) THEN
1050          zx_tmp_fi2d = solsw0*swradcorr
1051       ENDIF
1052       CALL histwrite_phy(o_sols0, zx_tmp_fi2d)
1053       CALL histwrite_phy(o_soll, sollw)
1054       CALL histwrite_phy(o_soll0, sollw0)
1055       CALL histwrite_phy(o_radsol, radsol)
1056
1057       IF (vars_defined) THEN
1058          zx_tmp_fi2d(:) = swup(:,1)*swradcorr(:)
1059       ENDIF
1060       CALL histwrite_phy(o_SWupSFC, zx_tmp_fi2d)
1061
1062       IF (vars_defined) THEN
1063          zx_tmp_fi2d(:) = swup0(:,1)*swradcorr(:)
1064       ENDIF
1065       CALL histwrite_phy(o_SWupSFCclr, zx_tmp_fi2d)
1066
1067       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
1068          IF (vars_defined) THEN
1069             zx_tmp_fi2d(:) = swupc0(:,1)*swradcorr(:)
1070          ENDIF
1071          CALL histwrite_phy(o_SWupSFCcleanclr, zx_tmp_fi2d)
1072       ENDIF
1073
1074       IF (vars_defined) THEN
1075          zx_tmp_fi2d(:) = swdn(:,1)*swradcorr(:)
1076       ENDIF
1077       CALL histwrite_phy(o_SWdnSFC, zx_tmp_fi2d)
1078
1079       IF (vars_defined) THEN
1080          zx_tmp_fi2d(:) = swdn0(:,1)*swradcorr(:)
1081       ENDIF
1082       CALL histwrite_phy(o_SWdnSFCclr, zx_tmp_fi2d)
1083
1084       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
1085          IF (vars_defined) THEN
1086             zx_tmp_fi2d(:) = swdnc0(:,1)*swradcorr(:)
1087          ENDIF
1088          CALL histwrite_phy(o_SWdnSFCcleanclr, zx_tmp_fi2d)
1089       ENDIF
1090
1091       CALL histwrite_phy(o_fdiffSWdnSFC, solswfdiff)
1092
1093       IF (vars_defined) THEN
1094          zx_tmp_fi2d(:)=sollwdown(:)-sollw(:)
1095       ENDIF
1096       CALL histwrite_phy(o_LWupSFC, zx_tmp_fi2d)
1097       CALL histwrite_phy(o_LWdnSFC, sollwdown)
1098
1099       IF (vars_defined) THEN
1100          sollwdownclr(1:klon) = -1.*lwdn0(1:klon,1)
1101          zx_tmp_fi2d(1:klon)=sollwdownclr(1:klon)-sollw0(1:klon)
1102       ENDIF
1103       CALL histwrite_phy(o_LWupSFCclr, zx_tmp_fi2d)
1104       CALL histwrite_phy(o_LWdnSFCclr, sollwdownclr)
1105       
1106       IF (vars_defined) THEN
1107          zx_tmp_fi2d(:) = lwup(:,klevp1)
1108       ENDIF
1109       CALL histwrite_phy(o_LWupTOA, zx_tmp_fi2d)
1110       
1111       IF (vars_defined) THEN
1112          zx_tmp_fi2d(:) = lwup0(:,klevp1)
1113       ENDIF
1114       CALL histwrite_phy(o_LWupTOAclr, zx_tmp_fi2d)
1115
1116       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
1117          IF (vars_defined) THEN
1118             zx_tmp_fi2d(:) = lwupc0(:,klevp1)
1119          ENDIF
1120          CALL histwrite_phy(o_LWupTOAcleanclr, zx_tmp_fi2d)
1121       ENDIF
1122
1123       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
1124          IF (vars_defined) THEN
1125             zx_tmp_fi2d(:) = -1.*lwdnc0(:,1)
1126          ENDIF
1127          CALL histwrite_phy(o_LWdnSFCcleanclr, zx_tmp_fi2d)
1128       ENDIF
1129
1130!AI 08 2023 Ecrad 3Deffect
1131#ifdef CPP_ECRAD
1132     CALL histwrite_phy(o_cloud_cover_sw, cloud_cover_sw)
1133     IF (ok_3Deffect) THEN
1134       CALL histwrite_phy(o_cloud_cover_sw_s2, cloud_cover_sw_s2)
1135       IF (vars_defined) THEN
1136          zx_tmp_fi2d = solsw_s2*swradcorr
1137       ENDIF
1138       CALL histwrite_phy(o_sols_s2, zx_tmp_fi2d)
1139       IF (vars_defined) THEN
1140          zx_tmp_fi2d = solsw0_s2*swradcorr
1141       ENDIF
1142       CALL histwrite_phy(o_sols0_s2, zx_tmp_fi2d)
1143       CALL histwrite_phy(o_soll_s2, sollw_s2)
1144       CALL histwrite_phy(o_soll0_s2, sollw0_s2)
1145       IF (vars_defined) THEN
1146         zx_tmp_fi2d = topsw_s2*swradcorr
1147       ENDIF
1148       CALL histwrite_phy(o_tops_s2, zx_tmp_fi2d)
1149
1150       IF (vars_defined) THEN
1151         zx_tmp_fi2d = topsw0_s2*swradcorr
1152       ENDIF
1153       CALL histwrite_phy(o_tops0_s2, zx_tmp_fi2d)
1154
1155       CALL histwrite_phy(o_topl_s2, toplw_s2)
1156       CALL histwrite_phy(o_topl0_s2, toplw0_s2)
1157
1158       IF (vars_defined) THEN
1159          zx_tmp_fi2d(:) = swup_s2(:,klevp1)*swradcorr(:)
1160       ENDIF
1161       CALL histwrite_phy(o_SWupTOA_s2, zx_tmp_fi2d)
1162
1163       IF (vars_defined) THEN
1164          zx_tmp_fi2d(:) = swup0_s2(:,klevp1)*swradcorr(:)
1165       ENDIF
1166       CALL histwrite_phy(o_SWupTOAclr_s2, zx_tmp_fi2d)
1167
1168       IF (vars_defined) THEN
1169          zx_tmp_fi2d(:) = swdn_s2(:,klevp1)*swradcorr(:)
1170       ENDIF
1171       CALL histwrite_phy(o_SWdnTOA_s2, zx_tmp_fi2d)
1172
1173       IF (vars_defined) THEN
1174          zx_tmp_fi2d(:) = swdn0_s2(:,klevp1)*swradcorr(:)
1175       ENDIF
1176       CALL histwrite_phy(o_SWdnTOAclr_s2, zx_tmp_fi2d)
1177
1178       IF (vars_defined) THEN
1179          zx_tmp_fi2d(:)=sollwdown_s2(:)-sollw_s2(:)
1180       ENDIF
1181       CALL histwrite_phy(o_LWupSFC_s2, zx_tmp_fi2d)
1182       CALL histwrite_phy(o_LWdnSFC_s2, sollwdown_s2)
1183
1184       IF (vars_defined) THEN
1185          sollwdownclr_s2(1:klon) = -1.*lwdn0_s2(1:klon,1)
1186          zx_tmp_fi2d(1:klon)=sollwdownclr_s2(1:klon)-sollw0_s2(1:klon)
1187       ENDIF
1188       CALL histwrite_phy(o_LWupSFCclr_s2, zx_tmp_fi2d)
1189       CALL histwrite_phy(o_LWdnSFCclr_s2, sollwdownclr_s2)
1190
1191       IF (vars_defined) THEN
1192          zx_tmp_fi2d(:) = swup_s2(:,1)*swradcorr(:)
1193       ENDIF
1194       CALL histwrite_phy(o_SWupSFC_s2, zx_tmp_fi2d)
1195
1196       IF (vars_defined) THEN
1197          zx_tmp_fi2d(:) = swup0_s2(:,1)*swradcorr(:)
1198       ENDIF
1199       CALL histwrite_phy(o_SWupSFCclr_s2, zx_tmp_fi2d)
1200
1201       IF (vars_defined) THEN
1202          zx_tmp_fi2d(:) = swdn_s2(:,1)*swradcorr(:)
1203       ENDIF
1204       CALL histwrite_phy(o_SWdnSFC_s2, zx_tmp_fi2d)
1205
1206       IF (vars_defined) THEN
1207          zx_tmp_fi2d(:) = swdn0_s2(:,1)*swradcorr(:)
1208       ENDIF
1209       CALL histwrite_phy(o_SWdnSFCclr_s2, zx_tmp_fi2d)
1210
1211       IF (vars_defined) THEN
1212         DO k=1, klevp1
1213           zx_tmp_fi3d1(:,k)=swup_s2(:,k)*swradcorr(:)
1214         ENDDO
1215       ENDIF
1216       CALL histwrite_phy(o_rsu_s2, zx_tmp_fi3d1)
1217
1218       IF (vars_defined) THEN
1219         DO k=1, klevp1
1220           zx_tmp_fi3d1(:,k)=swdn_s2(:,k)*swradcorr(:)
1221         ENDDO
1222       ENDIF
1223       CALL histwrite_phy(o_rsd_s2, zx_tmp_fi3d1)
1224
1225       IF (vars_defined) THEN
1226         DO k=1, klevp1
1227           zx_tmp_fi3d1(:,k)=swup0_s2(:,k)*swradcorr(:)
1228         ENDDO
1229       ENDIF
1230       CALL histwrite_phy(o_rsucs_s2, zx_tmp_fi3d1)
1231
1232       IF (vars_defined) THEN
1233         DO k=1, klevp1
1234           zx_tmp_fi3d1(:,k)=swdn0_s2(:,k)*swradcorr(:)
1235         ENDDO
1236       ENDIF
1237       CALL histwrite_phy(o_rsdcs_s2, zx_tmp_fi3d1)
1238
1239       CALL histwrite_phy(o_rlu_s2, lwup_s2)
1240       CALL histwrite_phy(o_rld_s2, lwdn_s2)
1241       CALL histwrite_phy(o_rlucs_s2, lwup0_s2)
1242       CALL histwrite_phy(o_rldcs_s2, lwdn0_s2)
1243    ENDIF !ok_3Deffect
1244#endif       
1245
1246       CALL histwrite_phy(o_bils, bils)
1247       CALL histwrite_phy(o_bils_diss, bils_diss)
1248       CALL histwrite_phy(o_bils_ec, bils_ec)
1249       CALL histwrite_phy(o_bils_ech, bils_ech)
1250       CALL histwrite_phy(o_bils_tke, bils_tke)
1251       CALL histwrite_phy(o_bils_kinetic, bils_kinetic)
1252       CALL histwrite_phy(o_bils_latent, bils_latent)
1253       CALL histwrite_phy(o_bils_enthalp, bils_enthalp)
1254
1255       IF (vars_defined) THEN
1256          zx_tmp_fi2d(1:klon)=-1*sens(1:klon)
1257       ENDIF
1258       CALL histwrite_phy(o_sens, zx_tmp_fi2d)
1259       CALL histwrite_phy(o_fder, fder)
1260       CALL histwrite_phy(o_ffonte, zxffonte)
1261       CALL histwrite_phy(o_fqcalving, zxfqcalving)
1262       CALL histwrite_phy(o_fqfonte, zxfqfonte)
1263       IF (vars_defined) THEN
1264          zx_tmp_fi2d(1:klon)=(zxfqfonte(1:klon)+rain_fall(1:klon))*pctsrf(1:klon,is_lic)
1265       ENDIF
1266       CALL histwrite_phy(o_mrroli, zx_tmp_fi2d)
1267       CALL histwrite_phy(o_runofflic, zxrunofflic)
1268       IF (vars_defined) THEN
1269          zx_tmp_fi2d=0.
1270          DO nsrf=1,nbsrf
1271             zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxu(:,1,nsrf)
1272          ENDDO
1273       ENDIF
1274       CALL histwrite_phy(o_taux, zx_tmp_fi2d)
1275
1276       IF (vars_defined) THEN
1277          zx_tmp_fi2d=0.
1278          DO nsrf=1,nbsrf
1279             zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxv(:,1,nsrf)
1280          ENDDO
1281       ENDIF
1282       CALL histwrite_phy(o_tauy, zx_tmp_fi2d)
1283
1284       DO nsrf = 1, nbsrf
1285
1286          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100.
1287          CALL histwrite_phy(o_pourc_srf(nsrf), zx_tmp_fi2d)
1288          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)
1289          CALL histwrite_phy(o_fract_srf(nsrf), zx_tmp_fi2d)
1290          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf)
1291          CALL histwrite_phy(o_taux_srf(nsrf), zx_tmp_fi2d)
1292          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf)
1293          CALL histwrite_phy(o_tauy_srf(nsrf), zx_tmp_fi2d)
1294          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf)
1295          CALL histwrite_phy(o_tsol_srf(nsrf), zx_tmp_fi2d)
1296          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = evap_pot( 1 : klon, nsrf)
1297          CALL histwrite_phy(o_evappot_srf(nsrf), zx_tmp_fi2d)
1298          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = ustar(1 : klon, nsrf)
1299          CALL histwrite_phy(o_ustar_srf(nsrf), zx_tmp_fi2d)
1300          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = u10m(1 : klon, nsrf)
1301          CALL histwrite_phy(o_u10m_srf(nsrf), zx_tmp_fi2d)
1302          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = v10m(1 : klon, nsrf)
1303          CALL histwrite_phy(o_v10m_srf(nsrf), zx_tmp_fi2d)
1304          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = t2m(1 : klon, nsrf)
1305          CALL histwrite_phy(o_t2m_srf(nsrf), zx_tmp_fi2d)
1306          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fevap(1 : klon, nsrf)
1307          CALL histwrite_phy(o_evap_srf(nsrf), zx_tmp_fi2d)
1308          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf)
1309          CALL histwrite_phy(o_sens_srf(nsrf), zx_tmp_fi2d)
1310          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf)
1311          CALL histwrite_phy(o_lat_srf(nsrf), zx_tmp_fi2d)
1312          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fsollw( 1 : klon, nsrf)
1313          CALL histwrite_phy(o_flw_srf(nsrf), zx_tmp_fi2d)
1314          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, nsrf)
1315          CALL histwrite_phy(o_fsw_srf(nsrf), zx_tmp_fi2d)
1316          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = wfbils( 1 : klon, nsrf)
1317          CALL histwrite_phy(o_wbils_srf(nsrf), zx_tmp_fi2d)
1318          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = (fevap(1:klon,nsrf)-(rain_fall(1:klon)+snow_fall(1:klon)))*pctsrf(1:klon,nsrf)
1319          CALL histwrite_phy(o_wbilo_srf(nsrf), zx_tmp_fi2d)
1320          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = wfevap( 1 : klon, nsrf)
1321          CALL histwrite_phy(o_wevap_srf(nsrf), zx_tmp_fi2d)
1322          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = rain_fall(1:klon)*pctsrf(1:klon,nsrf)
1323          CALL histwrite_phy(o_wrain_srf(nsrf), zx_tmp_fi2d)
1324          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = snow_fall(1:klon)*pctsrf(1:klon,nsrf)
1325          CALL histwrite_phy(o_wsnow_srf(nsrf), zx_tmp_fi2d)
1326
1327          IF (iflag_pbl > 1) THEN
1328             CALL histwrite_phy(o_tke_srf(nsrf),  pbl_tke(:,1:klev,nsrf))
1329             !CALL histwrite_phy(o_l_mix(nsrf),  l_mix(:,1:klev,nsrf))
1330             CALL histwrite_phy(o_l_mixmin(nsrf),  l_mixmin(:,1:klev,nsrf))
1331             CALL histwrite_phy(o_tke_max_srf(nsrf),  pbl_tke(:,1:klev,nsrf))
1332          ENDIF
1333!jyg<
1334          IF (iflag_pbl > 1 .AND. iflag_wake>=1  .AND. iflag_pbl_split >=1) THEN
1335             CALL histwrite_phy(o_dltpbltke_srf(nsrf), wake_delta_pbl_TKE(:,1:klev,nsrf))
1336          ENDIF
1337!>jyg
1338!          IF (iflag_pbl > 1 .AND. ifl_pbltree  >=1 ) THEN
1339!       CALL histwrite_phy(o_treedrg_srf(nsrf), treedrg(:,1:klev,nsrf))
1340!            ENDIF
1341
1342       ENDDO
1343
1344
1345        IF (iflag_pbl > 1) THEN
1346          zx_tmp_fi3d=0.
1347          IF (vars_defined) THEN
1348             DO nsrf=1,nbsrf
1349                DO k=1,klev
1350                   zx_tmp_fi3d(:,k)=zx_tmp_fi3d(:,k) &
1351                        +pctsrf(:,nsrf)*pbl_eps(:,k,nsrf)
1352                ENDDO
1353             ENDDO
1354          ENDIF
1355         
1356          CALL histwrite_phy(o_tke_dissip, zx_tmp_fi3d)   
1357
1358          zx_tmp_fi3d=0.
1359          IF (vars_defined) THEN
1360             DO nsrf=1,nbsrf
1361                DO k=1,klev
1362                   zx_tmp_fi3d(:,k)=zx_tmp_fi3d(:,k) &
1363                        +pctsrf(:,nsrf)*tke_shear(:,k,nsrf)
1364                ENDDO
1365             ENDDO
1366          ENDIF
1367
1368          CALL histwrite_phy(o_tke_shear, zx_tmp_fi3d)
1369
1370          zx_tmp_fi3d=0.
1371          IF (vars_defined) THEN
1372             DO nsrf=1,nbsrf
1373                DO k=1,klev
1374                   zx_tmp_fi3d(:,k)=zx_tmp_fi3d(:,k) &
1375                        +pctsrf(:,nsrf)*tke_buoy(:,k,nsrf)
1376                ENDDO
1377             ENDDO
1378          ENDIF
1379
1380          CALL histwrite_phy(o_tke_buoy, zx_tmp_fi3d)
1381
1382
1383          zx_tmp_fi3d=0.
1384          IF (vars_defined) THEN
1385             DO nsrf=1,nbsrf
1386                DO k=1,klev
1387                   zx_tmp_fi3d(:,k)=zx_tmp_fi3d(:,k) &
1388                        +pctsrf(:,nsrf)*tke_trans(:,k,nsrf)
1389                ENDDO
1390             ENDDO
1391          ENDIF
1392
1393          CALL histwrite_phy(o_tke_trans, zx_tmp_fi3d)
1394
1395       ENDIF
1396
1397       IF (vars_defined) zx_tmp_fi2d(1 : klon) = sens_prec_liq_o(1 : klon, 1)
1398       CALL histwrite_phy(o_sens_prec_liq_oce, zx_tmp_fi2d)       
1399       IF (vars_defined) zx_tmp_fi2d(1 : klon) = sens_prec_liq_o(1 : klon, 2)
1400       CALL histwrite_phy(o_sens_prec_liq_sic, zx_tmp_fi2d)       
1401       IF (vars_defined) zx_tmp_fi2d(1 : klon) = sens_prec_sol_o(1 : klon, 1)
1402       CALL histwrite_phy(o_sens_prec_sol_oce, zx_tmp_fi2d)       
1403       IF (vars_defined) zx_tmp_fi2d(1 : klon) = sens_prec_sol_o(1 : klon, 2)
1404       CALL histwrite_phy(o_sens_prec_sol_sic, zx_tmp_fi2d)       
1405
1406       IF (vars_defined) zx_tmp_fi2d(1 : klon) = lat_prec_liq_o(1 : klon, 1)
1407       CALL histwrite_phy(o_lat_prec_liq_oce, zx_tmp_fi2d)       
1408       IF (vars_defined) zx_tmp_fi2d(1 : klon) = lat_prec_liq_o(1 : klon, 2)
1409       CALL histwrite_phy(o_lat_prec_liq_sic, zx_tmp_fi2d)       
1410       IF (vars_defined) zx_tmp_fi2d(1 : klon) = lat_prec_sol_o(1 : klon, 1)
1411       CALL histwrite_phy(o_lat_prec_sol_oce, zx_tmp_fi2d)       
1412       IF (vars_defined) zx_tmp_fi2d(1 : klon) = lat_prec_sol_o(1 : klon, 2)
1413       CALL histwrite_phy(o_lat_prec_sol_sic, zx_tmp_fi2d)       
1414
1415       DO nsrf=1,nbsrf+1
1416          CALL histwrite_phy(o_wstar(nsrf), wstar(1 : klon, nsrf))
1417       ENDDO
1418
1419       CALL histwrite_phy(o_cdrm, cdragm)
1420       CALL histwrite_phy(o_cdrh, cdragh)
1421       CALL histwrite_phy(o_cldl, cldl)
1422       CALL histwrite_phy(o_cldm, cldm)
1423       CALL histwrite_phy(o_cldh, cldh)
1424       CALL histwrite_phy(o_cldt, cldt)
1425       CALL histwrite_phy(o_JrNt, JrNt)
1426       
1427       IF (vars_defined)  zx_tmp_fi2d=cldl*JrNt     
1428       CALL histwrite_phy(o_cldljn, zx_tmp_fi2d)
1429       
1430       IF (vars_defined)  zx_tmp_fi2d=cldm*JrNt     
1431       CALL histwrite_phy(o_cldmjn, zx_tmp_fi2d)
1432       
1433       IF (vars_defined)  zx_tmp_fi2d=cldh*JrNt
1434       CALL histwrite_phy(o_cldhjn, zx_tmp_fi2d)
1435       
1436       IF (vars_defined)  zx_tmp_fi2d=cldt*JrNt
1437       CALL histwrite_phy(o_cldtjn, zx_tmp_fi2d)
1438       
1439       CALL histwrite_phy(o_cldq, cldq)
1440       IF (vars_defined)       zx_tmp_fi2d(1:klon) = flwp(1:klon)
1441       CALL histwrite_phy(o_lwp, zx_tmp_fi2d)
1442       IF (vars_defined)       zx_tmp_fi2d(1:klon) = fiwp(1:klon)
1443       CALL histwrite_phy(o_iwp, zx_tmp_fi2d)
1444       CALL histwrite_phy(o_ue, ue)
1445       CALL histwrite_phy(o_ve, ve)
1446       CALL histwrite_phy(o_uq, uq)
1447       CALL histwrite_phy(o_vq, vq)
1448       CALL histwrite_phy(o_uwat, uwat)
1449       CALL histwrite_phy(o_vwat, vwat)
1450       IF (iflag_con.GE.3) THEN ! sb
1451          CALL histwrite_phy(o_cape, cape)
1452          CALL histwrite_phy(o_pbase, ema_pcb)
1453          CALL histwrite_phy(o_ptop, ema_pct)
1454          CALL histwrite_phy(o_fbase, ema_cbmf)
1455          IF (iflag_con /= 30) THEN
1456             CALL histwrite_phy(o_plcl, plcl)
1457             CALL histwrite_phy(o_plfc, plfc)
1458             CALL histwrite_phy(o_wbeff, wbeff)
1459             CALL histwrite_phy(o_convoccur, convoccur)
1460          ENDIF
1461
1462          CALL histwrite_phy(o_cape_max, cape)
1463
1464          CALL histwrite_phy(o_upwd, upwd)
1465          CALL histwrite_phy(o_Ma, Ma)
1466          CALL histwrite_phy(o_dnwd, dnwd)
1467          CALL histwrite_phy(o_dnwd0, dnwd0)
1468          !! The part relative to the frequency of occurence of convection
1469          !! is now grouped with the part relative to thermals and shallow
1470          !! convection (output of the 3 fields: ftime_deepcv, ftime_th and
1471          !!  ftime_con).
1472          IF (vars_defined) THEN
1473             IF (iflag_thermals>=1)THEN
1474                zx_tmp_fi3d=dnwd+dnwd0+upwd+fm_therm(:,1:klev)
1475             ELSE
1476                zx_tmp_fi3d=dnwd+dnwd0+upwd
1477             ENDIF
1478          ENDIF
1479          CALL histwrite_phy(o_mc, zx_tmp_fi3d)
1480       ENDIF !iflag_con .GE. 3
1481       CALL histwrite_phy(o_prw, prw)
1482       CALL histwrite_phy(o_prlw, prlw)
1483       CALL histwrite_phy(o_prsw, prsw)
1484       IF (ok_bs) THEN
1485       CALL histwrite_phy(o_prbsw, prbsw)
1486       ENDIF
1487       CALL histwrite_phy(o_water_budget, water_budget)
1488       CALL histwrite_phy(o_s_pblh, s_pblh)
1489       CALL histwrite_phy(o_s_pblt, s_pblt)
1490       CALL histwrite_phy(o_s_lcl, s_lcl)
1491       CALL histwrite_phy(o_s_therm, s_therm)
1492       !IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
1493       !       IF (o_s_capCL%flag(iff)<=lev_files(iff)) THEN
1494       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1495       !    $o_s_capCL%name,itau_w,s_capCL)
1496       !       ENDIF
1497       !       IF (o_s_oliqCL%flag(iff)<=lev_files(iff)) THEN
1498       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1499       !    $o_s_oliqCL%name,itau_w,s_oliqCL)
1500       !       ENDIF
1501       !       IF (o_s_cteiCL%flag(iff)<=lev_files(iff)) THEN
1502       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1503       !    $o_s_cteiCL%name,itau_w,s_cteiCL)
1504       !       ENDIF
1505       !       IF (o_s_trmb1%flag(iff)<=lev_files(iff)) THEN
1506       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1507       !    $o_s_trmb1%name,itau_w,s_trmb1)
1508       !       ENDIF
1509       !       IF (o_s_trmb2%flag(iff)<=lev_files(iff)) THEN
1510       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1511       !    $o_s_trmb2%name,itau_w,s_trmb2)
1512       !       ENDIF
1513       !       IF (o_s_trmb3%flag(iff)<=lev_files(iff)) THEN
1514       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1515       !    $o_s_trmb3%name,itau_w,s_trmb3)
1516       !       ENDIF
1517
1518       IF (.NOT. using_xios) THEN
1519         IF (.NOT.ok_all_xml) THEN
1520           ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
1521           ! Champs interpolles sur des niveaux de pression
1522            DO iff=1, nfiles
1523              ll=0
1524              DO k=1, nlevSTD
1525                bb2=clevSTD(k)
1526                  IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
1527                       bb2.EQ."500".OR.bb2.EQ."200".OR. &
1528                       bb2.EQ."100".OR. &
1529                       bb2.EQ."50".OR.bb2.EQ."10") THEN
1530
1531                      ! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1532                      ll=ll+1
1533                      CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
1534                      CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
1535                      CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
1536                      CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
1537                      CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
1538                      CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
1539
1540                  ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
1541              ENDDO
1542            ENDDO
1543         ENDIF
1544       ENDIF
1545
1546
1547       IF (using_xios) THEN
1548         IF (ok_all_xml) THEN
1549           !XIOS  CALL xios_get_field_attr("u850",default_value=missing_val)
1550!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1551            ll=0
1552            DO k=1, nlevSTD
1553              bb2=clevSTD(k)
1554              IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
1555                  bb2.EQ."500".OR.bb2.EQ."200".OR. &
1556                  bb2.EQ."100".OR. &
1557                  bb2.EQ."50".OR.bb2.EQ."10") THEN
1558                  ll=ll+1
1559                  CALL histwrite_phy(o_uSTDlevs(ll),ulevSTD(:,k))
1560                  CALL histwrite_phy(o_vSTDlevs(ll),vlevSTD(:,k))
1561                  CALL histwrite_phy(o_wSTDlevs(ll),wlevSTD(:,k))
1562                  CALL histwrite_phy(o_zSTDlevs(ll),philevSTD(:,k))
1563                  CALL histwrite_phy(o_qSTDlevs(ll),qlevSTD(:,k))
1564                  CALL histwrite_phy(o_tSTDlevs(ll),tlevSTD(:,k))
1565              ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
1566            ENDDO
1567         ENDIF
1568       ENDIF
1569
1570       IF (vars_defined) THEN
1571          DO i=1, klon
1572             IF (pctsrf(i,is_oce).GT.epsfra.OR. &
1573                  pctsrf(i,is_sic).GT.epsfra) THEN
1574                zx_tmp_fi2d(i) = (ftsol(i, is_oce) * pctsrf(i,is_oce)+ &
1575                     ftsol(i, is_sic) * pctsrf(i,is_sic))/ &
1576                     (pctsrf(i,is_oce)+pctsrf(i,is_sic))
1577             ELSE
1578                zx_tmp_fi2d(i) = 273.15
1579             ENDIF
1580          ENDDO
1581       ENDIF
1582       CALL histwrite_phy(o_t_oce_sic, zx_tmp_fi2d)
1583
1584       ! Couplage convection-couche limite
1585       IF (iflag_con.GE.3) THEN
1586          IF (iflag_coupl>=1) THEN
1587             CALL histwrite_phy(o_ale_bl, ale_bl)
1588             CALL histwrite_phy(o_alp_bl, alp_bl)
1589          ENDIF !iflag_coupl>=1
1590       ENDIF !(iflag_con.GE.3)
1591       ! Wakes
1592       IF (iflag_con.EQ.3) THEN
1593          CALL histwrite_phy(o_Mipsh, Mipsh)
1594          IF (iflag_wake>=1) THEN
1595             CALL histwrite_phy(o_ale_wk, ale_wake)
1596             CALL histwrite_phy(o_alp_wk, alp_wake)
1597             IF (iflag_pbl_split>=1) THEN
1598!!               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=dtvdf_x(1:klon,1:klev)/pdtphys
1599!!               CALL histwrite_phy(o_dtvdf_x    ,zx_tmp_fi3d)
1600!!               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=dtvdf_w(1:klon,1:klev)/pdtphys
1601!!               CALL histwrite_phy(o_dtvdf_w    ,zx_tmp_fi3d)
1602!!               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=dqvdf_x(1:klon,1:klev)/pdtphys
1603!!               CALL histwrite_phy(o_dqvdf_x    ,zx_tmp_fi3d)
1604!!               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=dqvdf_w(1:klon,1:klev)/pdtphys
1605!
1606               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_vdf_x(1:klon,1:klev)/pdtphys
1607               CALL histwrite_phy(o_dtvdf_x    ,zx_tmp_fi3d)
1608               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_vdf_w(1:klon,1:klev)/pdtphys
1609               CALL histwrite_phy(o_dtvdf_w    ,zx_tmp_fi3d)
1610               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_vdf_x(1:klon,1:klev)/pdtphys
1611               CALL histwrite_phy(o_dqvdf_x    ,zx_tmp_fi3d)
1612               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_vdf_w(1:klon,1:klev)/pdtphys
1613!
1614               CALL histwrite_phy(o_dqvdf_w    ,zx_tmp_fi3d)
1615       IF (vars_defined)  zx_tmp_fi2d(1:klon)=-1*sens_x(1:klon)
1616               CALL histwrite_phy(o_sens_x     ,zx_tmp_fi2d)
1617       IF (vars_defined)  zx_tmp_fi2d(1:klon)=-1*sens_w(1:klon)
1618               CALL histwrite_phy(o_sens_w     ,zx_tmp_fi2d)
1619               CALL histwrite_phy(o_flat_x     ,zxfluxlat_x)
1620               CALL histwrite_phy(o_flat_w     ,zxfluxlat_w)
1621          zx_tmp_fi2d=0.
1622          IF (vars_defined) THEN
1623             DO nsrf=1,nbsrf
1624                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:) &
1625                        +pctsrf(:,nsrf)*delta_tsurf(:,nsrf)
1626             ENDDO
1627          ENDIF
1628               CALL histwrite_phy(o_delta_tsurf,zx_tmp_fi2d)
1629               CALL histwrite_phy(o_cdragh_x   ,cdragh_x   )
1630               CALL histwrite_phy(o_cdragh_w   ,cdragh_w   )
1631               CALL histwrite_phy(o_cdragm_x   ,cdragm_x   )
1632               CALL histwrite_phy(o_cdragm_w   ,cdragm_w   )
1633               CALL histwrite_phy(o_kh         ,kh         )
1634               CALL histwrite_phy(o_kh_x       ,kh_x       )
1635          CALL histwrite_phy(o_strig, strig)
1636          CALL histwrite_phy(o_zcong, zcong)
1637          CALL histwrite_phy(o_zlcl_th, zlcl_th)
1638               CALL histwrite_phy(o_kh_w       ,kh_w       )
1639             ENDIF   ! (iflag_pbl_split>=1)
1640             CALL histwrite_phy(o_ale, ale)
1641             CALL histwrite_phy(o_alp, alp)
1642             CALL histwrite_phy(o_cin, cin)
1643             CALL histwrite_phy(o_WAPE, wake_pe)
1644             CALL histwrite_phy(o_cv_gen, cv_gen)
1645             CALL histwrite_phy(o_wake_h, wake_h)
1646             CALL histwrite_phy(o_wake_dens, wake_dens)
1647             CALL histwrite_phy(o_wake_s, wake_s)
1648             CALL histwrite_phy(o_wake_deltat, wake_deltat)
1649             CALL histwrite_phy(o_wake_deltaq, wake_deltaq)
1650             CALL histwrite_phy(o_wake_omg, wake_omg)
1651             IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_wake(1:klon,1:klev) &
1652                  /pdtphys
1653             CALL histwrite_phy(o_dtwak, zx_tmp_fi3d)
1654             IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_wake(1:klon,1:klev)/pdtphys
1655             CALL histwrite_phy(o_dqwak, zx_tmp_fi3d)
1656             IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1657             CALL histwrite_phy(o_dqwak2d, zx_tmp_fi2d)
1658          ENDIF ! iflag_wake>=1
1659          CALL histwrite_phy(o_ftd, ftd)
1660          CALL histwrite_phy(o_fqd, fqd)
1661       ENDIF !(iflag_con.EQ.3)
1662       IF (iflag_con.EQ.3.OR.iflag_con.EQ.30) THEN
1663          ! sortie RomP convection descente insaturee iflag_con=30
1664          ! etendue a iflag_con=3 (jyg)
1665          CALL histwrite_phy(o_Vprecip, Vprecip)
1666          CALL histwrite_phy(o_qtaa, qtaa)
1667          CALL histwrite_phy(o_clwaa, clw)
1668          CALL histwrite_phy(o_wdtrainA, wdtrainA)
1669          CALL histwrite_phy(o_wdtrainS, wdtrainS)
1670          CALL histwrite_phy(o_wdtrainM, wdtrainM)
1671       ENDIF !(iflag_con.EQ.3.or.iflag_con.EQ.30)
1672!!! nrlmd le 10/04/2012
1673       IF (iflag_trig_bl>=1) THEN
1674          CALL histwrite_phy(o_n2, n2)
1675          CALL histwrite_phy(o_s2, s2)
1676          CALL histwrite_phy(o_proba_notrig, proba_notrig)
1677          CALL histwrite_phy(o_random_notrig, random_notrig)
1678          CALL histwrite_phy(o_ale_bl_stat, ale_bl_stat)
1679          CALL histwrite_phy(o_ale_bl_trig, ale_bl_trig)
1680       ENDIF  !(iflag_trig_bl>=1)
1681       IF (iflag_clos_bl>=1) THEN
1682          CALL histwrite_phy(o_alp_bl_det, alp_bl_det)
1683          CALL histwrite_phy(o_alp_bl_fluct_m, alp_bl_fluct_m)
1684          CALL histwrite_phy(o_alp_bl_fluct_tke,  &
1685               alp_bl_fluct_tke)
1686          CALL histwrite_phy(o_alp_bl_conv, alp_bl_conv)
1687          CALL histwrite_phy(o_alp_bl_stat, alp_bl_stat)
1688       ENDIF  !(iflag_clos_bl>=1)
1689!!! fin nrlmd le 10/04/2012
1690       ! Output of slab ocean variables
1691       IF (type_ocean=='slab ') THEN
1692          CALL histwrite_phy(o_slab_bils, slab_wfbils)
1693          IF (nslay.EQ.1) THEN
1694              IF (vars_defined) zx_tmp_fi2d(:)=tslab(:,1)
1695              CALL histwrite_phy(o_tslab, zx_tmp_fi2d)
1696              IF (vars_defined) zx_tmp_fi2d(:)=dt_qflux(:,1)
1697              CALL histwrite_phy(o_slab_qflux, zx_tmp_fi2d)
1698          ELSE
1699              CALL histwrite_phy(o_tslab, tslab(:,1:nslay))
1700              CALL histwrite_phy(o_slab_qflux, dt_qflux(:,1:nslay))
1701          ENDIF
1702          IF (version_ocean=='sicINT') THEN
1703              CALL histwrite_phy(o_slab_bilg, slab_bilg)
1704              CALL histwrite_phy(o_slab_tice, tice)
1705              CALL histwrite_phy(o_slab_sic, seaice)
1706          ENDIF
1707          IF (slab_gm) THEN
1708             CALL histwrite_phy(o_slab_gm, dt_gm(:,1:nslay))
1709          ENDIF
1710          IF (slab_hdiff) THEN
1711            IF (nslay.EQ.1) THEN
1712                IF (vars_defined) zx_tmp_fi2d(:)=dt_hdiff(:,1)
1713                CALL histwrite_phy(o_slab_hdiff, zx_tmp_fi2d)
1714            ELSE
1715                CALL histwrite_phy(o_slab_hdiff, dt_hdiff(:,1:nslay))
1716            ENDIF
1717          ENDIF
1718          IF (slab_ekman.GT.0) THEN
1719            IF (nslay.EQ.1) THEN
1720                IF (vars_defined) zx_tmp_fi2d(:)=dt_ekman(:,1)
1721                CALL histwrite_phy(o_slab_ekman, zx_tmp_fi2d)
1722            ELSE
1723                CALL histwrite_phy(o_slab_ekman, dt_ekman(:,1:nslay))
1724            ENDIF
1725          ENDIF
1726       ENDIF !type_ocean == force/slab
1727       CALL histwrite_phy(o_weakinv, weak_inversion)
1728       CALL histwrite_phy(o_dthmin, dthmin)
1729       CALL histwrite_phy(o_cldtau, cldtau)
1730       CALL histwrite_phy(o_cldemi, cldemi)
1731       CALL histwrite_phy(o_pr_con_l, pmflxr(:,1:klev))
1732       CALL histwrite_phy(o_pr_con_i, pmflxs(:,1:klev))
1733       CALL histwrite_phy(o_pr_lsc_l, prfl(:,1:klev))
1734       CALL histwrite_phy(o_pr_lsc_i, psfl(:,1:klev))
1735       CALL histwrite_phy(o_re, re)
1736       CALL histwrite_phy(o_fl, fl)
1737
1738       IF (ok_bs) THEN
1739         CALL histwrite_phy(o_pr_bs, bsfl(:,1:klev))
1740       ENDIF
1741
1742       IF (vars_defined) THEN
1743          DO i=1, klon
1744             IF (zt2m(i).LE.273.15) then
1745                zx_tmp_fi2d(i)=MAX(0.,rh2m(i)*100.)
1746             ELSE
1747                zx_tmp_fi2d(i)=MAX(0.,MIN(100.,rh2m(i)*100.))
1748             ENDIF
1749          ENDDO
1750       ENDIF
1751       CALL histwrite_phy(o_rh2m, zx_tmp_fi2d)
1752
1753!       IF (vars_defined) THEN
1754!          DO i=1, klon
1755!             zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
1756!          ENDDO
1757!       ENDIF
1758!       CALL histwrite_phy(o_rh2m_min, zx_tmp_fi2d)
1759
1760!       IF (vars_defined) THEN
1761!          DO i=1, klon
1762!             zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
1763!          ENDDO
1764!       ENDIF
1765!       CALL histwrite_phy(o_rh2m_max, zx_tmp_fi2d)
1766
1767       CALL histwrite_phy(o_qsat2m, qsat2m)
1768       CALL histwrite_phy(o_tpot, tpot)
1769       CALL histwrite_phy(o_tpote, tpote)
1770       IF (vars_defined) zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, is_ter)
1771       CALL histwrite_phy(o_SWnetOR,  zx_tmp_fi2d)
1772       CALL histwrite_phy(o_LWdownOR, sollwdown)
1773       CALL histwrite_phy(o_snowl, snow_lsc)
1774       CALL histwrite_phy(o_solldown, sollwdown)
1775       CALL histwrite_phy(o_dtsvdfo, d_ts(:,is_oce))
1776       CALL histwrite_phy(o_dtsvdft, d_ts(:,is_ter))
1777       CALL histwrite_phy(o_dtsvdfg,  d_ts(:,is_lic))
1778       CALL histwrite_phy(o_dtsvdfi, d_ts(:,is_sic))
1779       CALL histwrite_phy(o_z0m, z0m(:,nbsrf+1))
1780       CALL histwrite_phy(o_z0h, z0h(:,nbsrf+1))
1781
1782       ! od550 per species
1783!--OLIVIER
1784!This is warranted by treating INCA aerosols as offline aerosols
1785#ifndef CPP_ECRAD
1786       IF (flag_aerosol.GT.0) THEN
1787          IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
1788
1789             CALL histwrite_phy(o_od443aer, od443aer)
1790             CALL histwrite_phy(o_od550aer, od550aer)
1791             CALL histwrite_phy(o_od865aer, od865aer)
1792             CALL histwrite_phy(o_abs550aer, abs550aer)
1793             CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
1794             CALL histwrite_phy(o_sconcso4, sconcso4)
1795             CALL histwrite_phy(o_sconcno3, sconcno3)
1796             CALL histwrite_phy(o_sconcoa, sconcoa)
1797             CALL histwrite_phy(o_sconcbc, sconcbc)
1798             CALL histwrite_phy(o_sconcss, sconcss)
1799             CALL histwrite_phy(o_sconcdust, sconcdust)
1800             CALL histwrite_phy(o_concso4, concso4)
1801             CALL histwrite_phy(o_concno3, concno3)
1802             CALL histwrite_phy(o_concoa, concoa)
1803             CALL histwrite_phy(o_concbc, concbc)
1804             CALL histwrite_phy(o_concss, concss)
1805             CALL histwrite_phy(o_concdust, concdust)
1806             CALL histwrite_phy(o_loadso4, loadso4)
1807             CALL histwrite_phy(o_loadoa, loadoa)
1808             CALL histwrite_phy(o_loadbc, loadbc)
1809             CALL histwrite_phy(o_loadss, loadss)
1810             CALL histwrite_phy(o_loaddust, loaddust)
1811             CALL histwrite_phy(o_loadno3, loadno3)
1812             CALL histwrite_phy(o_dryod550aer, dryod550aer)
1813             DO naero = 1, naero_tot-1
1814                CALL histwrite_phy(o_drytausumaero(naero),drytausum_aero(:,naero))
1815             ENDDO
1816          ENDIF
1817       ENDIF
1818       !--STRAT AER
1819       IF (flag_aerosol.GT.0.OR.flag_aerosol_strat.GT.0) THEN
1820          DO naero = 1, naero_tot
1821             CALL histwrite_phy(o_tausumaero(naero),tausum_aero(:,2,naero))
1822          ENDDO
1823       ENDIF
1824       IF (flag_aerosol_strat.GT.0) THEN
1825          CALL histwrite_phy(o_tausumaero_lw,tausum_aero(:,6,id_STRAT_phy))
1826       ENDIF
1827
1828       CALL histwrite_phy(o_p_tropopause, p_tropopause)
1829       CALL histwrite_phy(o_t_tropopause, t_tropopause)
1830       CALL histwrite_phy(o_z_tropopause, z_tropopause)
1831
1832! ThL -- In the following, we assume read_climoz == 1
1833       IF (vars_defined) THEN
1834         zx_tmp_fi2d = 0.0    ! Computation for strato, added ThL
1835         DO k=1, klev
1836            zx_tmp_fi2d(:) = zx_tmp_fi2d(:) + wo(:,k,1) * stratomask(:,k) * 1.e3
1837         ENDDO
1838       ENDIF
1839       CALL histwrite_phy(o_col_O3_strato, zx_tmp_fi2d) ! Added ThL
1840
1841       IF (vars_defined) THEN
1842         zx_tmp_fi2d = 0.0    ! Computation for tropo, added ThL
1843         DO k=1, klev
1844            zx_tmp_fi2d(:) = zx_tmp_fi2d(:) + wo(:,k,1) * (1.0-stratomask(:,k)) * 1.e3
1845         ENDDO
1846       ENDIF
1847       CALL histwrite_phy(o_col_O3_tropo, zx_tmp_fi2d)   ! Added ThL
1848! end add ThL
1849
1850IF (CPPKEY_STRATAER) THEN
1851       IF (type_trac=='coag') THEN
1852          CALL histwrite_phy(o_R2SO4, R2SO4)
1853          CALL histwrite_phy(o_OCS_lifetime, OCS_lifetime)
1854          CALL histwrite_phy(o_SO2_lifetime, SO2_lifetime)
1855          CALL histwrite_phy(o_budg_3D_backgr_ocs,   budg_3D_backgr_ocs)
1856          CALL histwrite_phy(o_budg_3D_backgr_so2,   budg_3D_backgr_so2)
1857          CALL histwrite_phy(o_budg_3D_ocs_to_so2,   budg_3D_ocs_to_so2)
1858          CALL histwrite_phy(o_budg_3D_so2_to_h2so4, budg_3D_so2_to_h2so4)
1859          CALL histwrite_phy(o_budg_3D_nucl,         budg_3D_nucl)
1860          CALL histwrite_phy(o_budg_3D_cond_evap,    budg_3D_cond_evap)
1861          CALL histwrite_phy(o_budg_dep_dry_ocs,     budg_dep_dry_ocs)
1862          CALL histwrite_phy(o_budg_dep_wet_ocs,     budg_dep_wet_ocs)
1863          CALL histwrite_phy(o_budg_dep_dry_so2,     budg_dep_dry_so2)
1864          CALL histwrite_phy(o_budg_dep_wet_so2,     budg_dep_wet_so2)
1865          CALL histwrite_phy(o_budg_dep_dry_h2so4,   budg_dep_dry_h2so4)
1866          CALL histwrite_phy(o_budg_dep_wet_h2so4,   budg_dep_wet_h2so4)
1867          CALL histwrite_phy(o_budg_dep_dry_part,    budg_dep_dry_part)
1868          CALL histwrite_phy(o_budg_dep_wet_part,    budg_dep_wet_part)
1869          CALL histwrite_phy(o_budg_emi_ocs,         budg_emi_ocs)
1870          CALL histwrite_phy(o_budg_emi_so2,         budg_emi_so2)
1871          CALL histwrite_phy(o_budg_emi_h2so4,       budg_emi_h2so4)
1872          CALL histwrite_phy(o_budg_emi_part,        budg_emi_part)
1873          CALL histwrite_phy(o_budg_ocs_to_so2,      budg_ocs_to_so2)
1874          CALL histwrite_phy(o_budg_so2_to_h2so4,    budg_so2_to_h2so4)
1875          CALL histwrite_phy(o_budg_h2so4_to_part,   budg_h2so4_to_part)
1876          CALL histwrite_phy(o_budg_sed_part,        budg_sed_part)
1877          CALL histwrite_phy(o_surf_PM25_sulf, surf_PM25_sulf)
1878          CALL histwrite_phy(o_vsed_aer, vsed_aer)
1879          CALL histwrite_phy(o_f_r_wet, f_r_wet)
1880          CALL histwrite_phy(o_ext_strat_550, tau_strat_550)
1881          CALL histwrite_phy(o_ext_strat_1020, tau_strat_1020)
1882          CALL histwrite_phy(o_tau_strat_550, tausum_strat(:,1))
1883          CALL histwrite_phy(o_tau_strat_1020, tausum_strat(:,2))
1884          CALL histwrite_phy(o_SAD_sulfate, SAD_sulfate)
1885          CALL histwrite_phy(o_reff_sulfate, reff_sulfate)
1886          CALL histwrite_phy(o_sulfmmr, sulfmmr)
1887          ! All BINs fields
1888          DO itr = 1, nbtr_bin
1889             CALL histwrite_phy(o_nd_mode(itr), nd_mode(:,:,itr))
1890             CALL histwrite_phy(o_sulfmmr_mode(itr), sulfmmr_mode(:,:,itr))
1891          ENDDO !--itr
1892       ENDIF
1893END IF
1894       !NL
1895       IF (ok_volcan .AND. ok_ade) THEN
1896          DO k=1, klev
1897             IF (vars_defined) zx_tmp_fi3d(:,k)=heat_volc(:,k)*swradcorr(:)
1898          ENDDO
1899          CALL histwrite_phy(o_heat_volc, zx_tmp_fi3d)
1900          DO k=1, klev
1901             IF (vars_defined) zx_tmp_fi3d(:,k)=cool_volc(:,k)
1902          ENDDO
1903          CALL histwrite_phy(o_cool_volc, zx_tmp_fi3d)
1904       ENDIF
1905       IF (ok_ade) THEN
1906          IF (vars_defined) zx_tmp_fi2d(:)=topswad_aero*swradcorr
1907          CALL histwrite_phy(o_topswad, zx_tmp_fi2d)
1908         
1909          IF (vars_defined) zx_tmp_fi2d(:)=topswad0_aero*swradcorr
1910          CALL histwrite_phy(o_topswad0, zx_tmp_fi2d)
1911                   
1912          IF (vars_defined) zx_tmp_fi2d(:)=solswad_aero*swradcorr
1913          CALL histwrite_phy(o_solswad, zx_tmp_fi2d)
1914                   
1915          IF (vars_defined) zx_tmp_fi2d(:)=solswad0_aero*swradcorr
1916          CALL histwrite_phy(o_solswad0, zx_tmp_fi2d)
1917         
1918          IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
1919
1920             CALL histwrite_phy(o_toplwad, toplwad_aero)
1921             CALL histwrite_phy(o_toplwad0, toplwad0_aero)
1922             CALL histwrite_phy(o_sollwad, sollwad_aero)
1923             CALL histwrite_phy(o_sollwad0, sollwad0_aero)
1924          ENDIF
1925          !====MS forcing diagnostics
1926          !ym warning : topsw_aero, solsw_aero, topsw0_aero, solsw0_aero are not defined by model
1927          !ym => init to 0 in radlwsw_m.F90 ztopsw_aero, zsolsw_aero, ztopsw0_aero, zsolsw0_aero
1928
1929          IF (vars_defined) zx_tmp_fi2d(:)=topsw_aero(:,1)*swradcorr(:)
1930          CALL histwrite_phy(o_swtoaas_nat,zx_tmp_fi2d)
1931          IF (vars_defined) zx_tmp_fi2d(:)=solsw_aero(:,1)*swradcorr(:)
1932          CALL histwrite_phy(o_swsrfas_nat,zx_tmp_fi2d)
1933          IF (vars_defined) zx_tmp_fi2d(:)=topsw0_aero(:,1)*swradcorr(:)
1934          CALL histwrite_phy(o_swtoacs_nat,zx_tmp_fi2d)
1935          IF (vars_defined) zx_tmp_fi2d(:)=solsw0_aero(:,1)*swradcorr(:)
1936          CALL histwrite_phy(o_swsrfcs_nat,zx_tmp_fi2d)
1937          !ant
1938          IF (vars_defined) zx_tmp_fi2d(:)=topsw_aero(:,2)*swradcorr(:)
1939          CALL histwrite_phy(o_swtoaas_ant,zx_tmp_fi2d)
1940          IF (vars_defined) zx_tmp_fi2d(:)=solsw_aero(:,2)*swradcorr(:)
1941          CALL histwrite_phy(o_swsrfas_ant,zx_tmp_fi2d)
1942          IF (vars_defined) zx_tmp_fi2d(:)=topsw0_aero(:,2)*swradcorr(:)
1943          CALL histwrite_phy(o_swtoacs_ant,zx_tmp_fi2d)
1944          IF (vars_defined) zx_tmp_fi2d(:)=solsw0_aero(:,2)*swradcorr(:)
1945          CALL histwrite_phy(o_swsrfcs_ant,zx_tmp_fi2d)
1946          !cf
1947          IF (.not. aerosol_couple) THEN
1948             IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,1)*swradcorr(:)
1949             CALL histwrite_phy(o_swtoacf_nat,zx_tmp_fi2d)
1950             IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,1)*swradcorr(:)
1951             CALL histwrite_phy(o_swsrfcf_nat,zx_tmp_fi2d)
1952             IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,2)*swradcorr(:)
1953             CALL histwrite_phy(o_swtoacf_ant,zx_tmp_fi2d)
1954             IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,2)*swradcorr(:)
1955             CALL histwrite_phy(o_swsrfcf_ant,zx_tmp_fi2d)
1956             IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,3)*swradcorr(:)
1957             CALL histwrite_phy(o_swtoacf_zero,zx_tmp_fi2d)
1958             IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,3)*swradcorr(:)
1959             CALL histwrite_phy(o_swsrfcf_zero,zx_tmp_fi2d)
1960          ENDIF
1961          !====MS forcing diagnostics
1962       ENDIF
1963       IF (ok_aie) THEN
1964          IF (vars_defined) zx_tmp_fi2d(:)= topswai_aero*swradcorr
1965          CALL histwrite_phy(o_topswai, zx_tmp_fi2d)
1966         
1967          IF (vars_defined) zx_tmp_fi2d(:)=toplwai_aero*swradcorr
1968          CALL histwrite_phy(o_toplwai, zx_tmp_fi2d)
1969         
1970          IF (vars_defined) zx_tmp_fi2d(:)=solswai_aero*swradcorr
1971          CALL histwrite_phy(o_solswai, zx_tmp_fi2d)
1972         
1973          IF (vars_defined) zx_tmp_fi2d(:)=sollwai_aero*swradcorr
1974          CALL histwrite_phy(o_sollwai, zx_tmp_fi2d)
1975       ENDIF
1976       IF (flag_aerosol.GT.0.AND.ok_cdnc) THEN
1977          CALL histwrite_phy(o_scdnc, scdnc)
1978          CALL histwrite_phy(o_cldncl, cldncl)
1979          CALL histwrite_phy(o_reffclws, reffclws)
1980          CALL histwrite_phy(o_reffclwc, reffclwc)
1981          CALL histwrite_phy(o_cldnvi, cldnvi)
1982          CALL histwrite_phy(o_lcc, lcc)
1983          CALL histwrite_phy(o_lcc3d, lcc3d)
1984          CALL histwrite_phy(o_lcc3dcon, lcc3dcon)
1985          CALL histwrite_phy(o_lcc3dstra, lcc3dstra)
1986          CALL histwrite_phy(o_icc3dcon, icc3dcon)
1987          CALL histwrite_phy(o_icc3dstra, icc3dstra)
1988          CALL histwrite_phy(o_cldicemxrat, zfice)
1989          IF (vars_defined) zx_tmp_fi3d(:,:)=1-zfice(:,:)
1990          CALL histwrite_phy(o_cldwatmxrat, zx_tmp_fi3d)
1991          CALL histwrite_phy(o_reffclwtop, reffclwtop)
1992       ENDIF
1993       ! Champs 3D:
1994       IF (ok_ade .OR. ok_aie) then
1995          IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
1996             CALL histwrite_phy(o_ec550aer, ec550aer)
1997          ENDIF
1998       ENDIF
1999
2000       CALL histwrite_phy(o_lwcon, flwc)
2001       CALL histwrite_phy(o_iwcon, fiwc)
2002       CALL histwrite_phy(o_temp, t_seri)
2003       CALL histwrite_phy(o_theta, theta)
2004       CALL histwrite_phy(o_ovapinit, qx(:,:,ivap))
2005       CALL histwrite_phy(o_ovap, q_seri)
2006       CALL histwrite_phy(o_oliq, ql_seri)
2007       !FC
2008       CALL histwrite_phy(o_zxfluxt, zxfluxt)
2009       CALL histwrite_phy(o_zxfluxq, zx_tmp_fi3d)
2010       !FC
2011
2012       IF (vars_defined) zx_tmp_fi3d = ql_seri+qs_seri
2013       CALL histwrite_phy(o_ocond, zx_tmp_fi3d)
2014     
2015       IF (vars_defined) zx_tmp_fi3d = qs_seri
2016       CALL histwrite_phy(o_oice, zx_tmp_fi3d)
2017
2018       CALL histwrite_phy(o_geop, zphi)
2019       CALL histwrite_phy(o_vitu, u_seri)
2020       CALL histwrite_phy(o_vitv, v_seri)
2021       CALL histwrite_phy(o_vitw, omega)
2022       CALL histwrite_phy(o_pres, pplay)
2023       CALL histwrite_phy(o_paprs, paprs(:,1:klev))
2024       
2025       IF (vars_defined) zx_tmp_fi3d = zphi/RG
2026       CALL histwrite_phy(o_zfull,zx_tmp_fi3d)
2027
2028       IF (ok_bs) THEN
2029          CALL histwrite_phy(o_qbs, qbs_seri)
2030       ENDIF
2031
2032       IF (using_xios) THEN
2033!solbnd begin
2034#ifdef CPP_RRTM
2035         IF (iflag_rrtm.EQ.1) THEN
2036           IF (vars_defined) THEN
2037             DO ISW=1, NSW
2038               zx_tmp_fi3dsp(:,ISW) = swdn(:,klevp1)*swradcorr(:)*RSUN(ISW)
2039             ENDDO
2040             CALL histwrite_phy(o_solbnd, zx_tmp_fi3dsp)
2041           ENDIF
2042         ENDIF
2043#endif
2044!solbnd end
2045       ENDIF
2046#endif
2047
2048       IF (flag_aerosol_strat.EQ.2) THEN
2049         CALL histwrite_phy(o_stratomask, stratomask)
2050       ENDIF
2051     
2052       IF (vars_defined)  THEN
2053        zx_tmp_fi3d(:,1)= pphis(:)/RG
2054        DO k = 2, klev
2055         DO i = 1, klon
2056            zx_tmp_fi3d(i,k) = zphi(i,k-1)/RG + &
2057                          (zphi(i,k)-zphi(i,k-1))/RG * &
2058                          (paprs(i,k)-pplay(i,k-1))/(pplay(i,k)-pplay(i,k-1))
2059         ENDDO
2060        ENDDO
2061       ENDIF
2062       CALL histwrite_phy(o_zhalf, zx_tmp_fi3d)
2063       CALL histwrite_phy(o_rneb, cldfra)
2064       CALL histwrite_phy(o_rnebcon, rnebcon)
2065       CALL histwrite_phy(o_rnebls, rneb)
2066       CALL histwrite_phy(o_rneblsvol, rneblsvol)
2067       IF (vars_defined)  THEN
2068          DO k=1, klev
2069             DO i=1, klon
2070                zx_tmp_fi3d(i,k)=cldfra(i,k)*JrNt(i)
2071             ENDDO
2072          ENDDO
2073       ENDIF
2074       CALL histwrite_phy(o_rnebjn, zx_tmp_fi3d)
2075       CALL histwrite_phy(o_rhum, zx_rh)
2076       IF (iflag_ice_thermo .GT. 0) THEN
2077          IF (vars_defined) zx_tmp_fi3d = zx_rhl * 100.
2078          CALL histwrite_phy(o_rhl, zx_tmp_fi3d)
2079          IF (vars_defined) zx_tmp_fi3d = zx_rhi * 100.
2080          CALL histwrite_phy(o_rhi, zx_tmp_fi3d)
2081       ENDIF
2082     
2083       IF (ok_new_lscp) THEN
2084           CALL histwrite_phy(o_pfraclr, pfraclr)
2085           CALL histwrite_phy(o_pfracld, pfracld)
2086           CALL histwrite_phy(o_cldfraliq, cldfraliq)
2087           CALL histwrite_phy(o_sigma2_icefracturb, sigma2_icefracturb)
2088           CALL histwrite_phy(o_mean_icefracturb, mean_icefracturb)
2089           IF (ok_poprecip) THEN
2090           CALL histwrite_phy(o_qrainlsc, qraindiag)
2091           CALL histwrite_phy(o_qsnowlsc, qsnowdiag)
2092           CALL histwrite_phy(o_dqreva, dqreva)
2093           CALL histwrite_phy(o_dqrauto, dqrauto)
2094           CALL histwrite_phy(o_dqrcol, dqrcol)
2095           CALL histwrite_phy(o_dqrmelt, dqrmelt)
2096           CALL histwrite_phy(o_dqrfreez, dqrfreez)
2097           CALL histwrite_phy(o_dqssub, dqssub)
2098           CALL histwrite_phy(o_dqsauto, dqsauto)
2099           CALL histwrite_phy(o_dqsagg, dqsagg)
2100           CALL histwrite_phy(o_dqsmelt, dqsmelt)
2101           CALL histwrite_phy(o_dqsfreez, dqsfreez)
2102           CALL histwrite_phy(o_dqsrim, dqsrim)
2103           IF ( ok_ice_sedim ) THEN
2104            CALL histwrite_phy(o_dqised, dqised)
2105            CALL histwrite_phy(o_dcfsed, dcfsed)
2106            CALL histwrite_phy(o_dqvcsed, dqvcsed)
2107           ENDIF
2108           ELSE
2109            CALL histwrite_phy(o_dqreva, dqreva)
2110            CALL histwrite_phy(o_dqssub, dqssub)
2111            CALL histwrite_phy(o_dqrauto, dqrauto)
2112            CALL histwrite_phy(o_dqsauto, dqsauto)
2113           ENDIF
2114       ENDIF
2115
2116!-- LSCP - condensation and supersaturation variables
2117       IF (ok_ice_supersat) THEN
2118         CALL histwrite_phy(o_cfseri, cf_seri)
2119         CALL histwrite_phy(o_dcfdyn, d_cf_dyn)
2120         CALL histwrite_phy(o_rvcseri, rvc_seri)
2121         CALL histwrite_phy(o_drvcdyn, d_rvc_dyn)
2122         CALL histwrite_phy(o_qsub, qsub)
2123         CALL histwrite_phy(o_qissr, qissr)
2124         CALL histwrite_phy(o_qcld, qcld)
2125         CALL histwrite_phy(o_subfra, subfra)
2126         CALL histwrite_phy(o_issrfra, issrfra)
2127         CALL histwrite_phy(o_gammacond, gamma_cond)
2128         CALL histwrite_phy(o_dcfsub, dcf_sub)
2129         CALL histwrite_phy(o_dcfcon, dcf_con)
2130         CALL histwrite_phy(o_dcfmix, dcf_mix)
2131         CALL histwrite_phy(o_dqiadj, dqi_adj)
2132         CALL histwrite_phy(o_dqisub, dqi_sub)
2133         CALL histwrite_phy(o_dqicon, dqi_con)
2134         CALL histwrite_phy(o_dqimix, dqi_mix)
2135         CALL histwrite_phy(o_dqvcadj, dqvc_adj)
2136         CALL histwrite_phy(o_dqvcsub, dqvc_sub)
2137         CALL histwrite_phy(o_dqvccon, dqvc_con)
2138         CALL histwrite_phy(o_dqvcmix, dqvc_mix)
2139         CALL histwrite_phy(o_qsatl, qsatliq)
2140         CALL histwrite_phy(o_qsati, qsatice)
2141         CALL histwrite_phy(o_issrfra100to150, issrfra100to150)
2142         CALL histwrite_phy(o_issrfra150to200, issrfra150to200)
2143         CALL histwrite_phy(o_issrfra200to250, issrfra200to250)
2144         CALL histwrite_phy(o_issrfra250to300, issrfra250to300)
2145         CALL histwrite_phy(o_issrfra300to400, issrfra300to400)
2146         CALL histwrite_phy(o_issrfra400to500, issrfra400to500)
2147       ENDIF
2148!-- LSCP - aviation variables
2149       IF (ok_plane_contrail) THEN
2150         CALL histwrite_phy(o_rcontseri, rcont_seri)
2151         CALL histwrite_phy(o_drcontdyn, d_rcont_dyn)
2152         CALL histwrite_phy(o_flight_dist, flight_dist)
2153         CALL histwrite_phy(o_Tcritcont, Tcritcont)
2154         CALL histwrite_phy(o_qcritcont, qcritcont)
2155         CALL histwrite_phy(o_potcontfraP, potcontfraP)
2156         CALL histwrite_phy(o_potcontfraNP, potcontfraNP)
2157         CALL histwrite_phy(o_contfra, contfra)
2158         CALL histwrite_phy(o_dcontfracir, dcontfra_cir)
2159         CALL histwrite_phy(o_dcfavi, dcf_avi)
2160         CALL histwrite_phy(o_dqiavi, dqi_avi)
2161         CALL histwrite_phy(o_dqvcavi, dqvc_avi)
2162         CALL histwrite_phy(o_cldfra_nocont, cldfra_nocont)
2163         CALL histwrite_phy(o_cldtau_nocont, cldtau_nocont)
2164         CALL histwrite_phy(o_cldemi_nocont, cldemi_nocont)
2165         CALL histwrite_phy(o_cldh_nocont, cldh_nocont)
2166         CALL histwrite_phy(o_contcov, contcov)
2167         CALL histwrite_phy(o_iwp_nocont, fiwp_nocont)
2168         CALL histwrite_phy(o_iwc_nocont, fiwc_nocont)
2169         CALL histwrite_phy(o_ref_ice_nocont, ref_ice_nocont)
2170         IF (ok_rad_contrail) THEN
2171           IF (vars_defined) zx_tmp_fi2d = topsw_nocont * swradcorr
2172           CALL histwrite_phy(o_tops_nocont, topsw_nocont)
2173           CALL histwrite_phy(o_topl_nocont, toplw_nocont)
2174           IF (vars_defined) zx_tmp_fi2d = topsw_nocont * swradcorr - toplw_nocont
2175           CALL histwrite_phy(o_nettop_nocont, zx_tmp_fi2d)
2176           IF (vars_defined) zx_tmp_fi2d = solsw_nocont * swradcorr
2177           CALL histwrite_phy(o_sols_nocont, solsw_nocont)
2178           CALL histwrite_phy(o_soll_nocont, sollw_nocont)
2179         ENDIF
2180       ENDIF
2181       IF (ok_plane_h2o) THEN
2182         CALL histwrite_phy(o_flight_h2o, flight_h2o)
2183         CALL histwrite_phy(o_dqavi, d_q_avi)
2184       ENDIF
2185       
2186       IF (vars_defined) zx_tmp_fi3d = wo(:, :, 1) * dobson_u * 1e3 / zmasse / rmo3 * rmd
2187       CALL histwrite_phy(o_ozone, zx_tmp_fi3d)
2188
2189       IF (read_climoz == 2) THEN
2190         IF (vars_defined) zx_tmp_fi3d = wo(:, :, 2) * dobson_u * 1e3 / zmasse / rmo3 * rmd
2191         CALL histwrite_phy(o_ozone_light, zx_tmp_fi3d)
2192       ENDIF
2193
2194       CALL histwrite_phy(o_duphy, d_u)
2195
2196       CALL histwrite_phy(o_dtphy, d_t)
2197
2198       CALL histwrite_phy(o_dqphy,  d_qx(:,:,ivap))
2199       IF (vars_defined) CALL water_int(klon,klev,d_qx(:,:,ivap),zmasse,zx_tmp_fi2d)
2200       CALL histwrite_phy(o_dqphy2d,  zx_tmp_fi2d)
2201
2202       CALL histwrite_phy(o_dqlphy,  d_qx(:,:,iliq))
2203       IF (vars_defined) CALL water_int(klon,klev,d_qx(:,:,iliq),zmasse,zx_tmp_fi2d)
2204       CALL histwrite_phy(o_dqlphy2d,  zx_tmp_fi2d)
2205
2206       IF (nqo.EQ.3) THEN
2207       CALL histwrite_phy(o_dqsphy,  d_qx(:,:,isol))
2208       IF (vars_defined) CALL water_int(klon,klev,d_qx(:,:,isol),zmasse,zx_tmp_fi2d)
2209       CALL histwrite_phy(o_dqsphy2d,  zx_tmp_fi2d)
2210       ELSE
2211       zx_tmp_fi3d=0.0
2212       CALL histwrite_phy(o_dqsphy,  zx_tmp_fi3d)
2213       zx_tmp_fi2d=0.0
2214       CALL histwrite_phy(o_dqsphy2d,  zx_tmp_fi2d)
2215       ENDIF
2216
2217
2218       IF (ok_bs) THEN
2219       CALL histwrite_phy(o_dqbsphy,  d_qx(:,:,ibs))
2220       IF (vars_defined) CALL water_int(klon,klev,d_qx(:,:,ibs),zmasse,zx_tmp_fi2d)
2221       CALL histwrite_phy(o_dqbsphy2d,  zx_tmp_fi2d)
2222       ELSE
2223       zx_tmp_fi3d=0.0
2224       CALL histwrite_phy(o_dqbsphy,  zx_tmp_fi3d)
2225       zx_tmp_fi2d=0.0
2226       CALL histwrite_phy(o_dqbsphy2d,  zx_tmp_fi2d)
2227       ENDIF
2228
2229       DO nsrf=1, nbsrf
2230          IF (vars_defined) zx_tmp_fi2d(1 : klon) = falb1( 1 : klon, nsrf)
2231          CALL histwrite_phy(o_albe_srf(nsrf), zx_tmp_fi2d)
2232          IF (vars_defined) zx_tmp_fi2d(1 : klon) = z0m( 1 : klon, nsrf)
2233          CALL histwrite_phy(o_z0m_srf(nsrf), zx_tmp_fi2d)
2234          IF (vars_defined) zx_tmp_fi2d(1 : klon) = z0h( 1 : klon, nsrf)
2235          CALL histwrite_phy(o_z0h_srf(nsrf), zx_tmp_fi2d)
2236          IF (vars_defined) zx_tmp_fi2d(1 : klon) = agesno( 1 : klon, nsrf)
2237          CALL histwrite_phy(o_ages_srf(nsrf), zx_tmp_fi2d)
2238          IF (vars_defined) zx_tmp_fi2d(1 : klon) = snow( 1 : klon, nsrf)
2239          CALL histwrite_phy(o_snow_srf(nsrf), zx_tmp_fi2d)
2240       ENDDO !nsrf=1, nbsrf
2241       CALL histwrite_phy(o_alb1, albsol1)
2242       CALL histwrite_phy(o_alb2, albsol2)
2243       !FH Sorties pour la couche limite
2244       IF (iflag_pbl>1) THEN
2245          zx_tmp_fi3d=0.
2246          IF (vars_defined) THEN
2247             DO nsrf=1,nbsrf
2248                DO k=1,klev
2249                   zx_tmp_fi3d(:,k)=zx_tmp_fi3d(:,k) &
2250                        +pctsrf(:,nsrf)*pbl_tke(:,k,nsrf)
2251                ENDDO
2252             ENDDO
2253          ENDIF
2254          CALL histwrite_phy(o_tke, zx_tmp_fi3d)
2255          CALL histwrite_phy(o_tke_max, zx_tmp_fi3d) 
2256       ENDIF
2257
2258       CALL histwrite_phy(o_kz, coefh(:,:,is_ave))
2259
2260       CALL histwrite_phy(o_kz_max, coefh(:,:,is_ave))
2261
2262       CALL histwrite_phy(o_clwcon, clwcon0)
2263
2264       CALL histwrite_phy(o_dtdyn, d_t_dyn)
2265
2266       CALL histwrite_phy(o_dqdyn, d_q_dyn)
2267
2268       CALL histwrite_phy(o_dqdyn2d,d_q_dyn2d)
2269
2270       CALL histwrite_phy(o_dqldyn, d_ql_dyn)
2271
2272       CALL histwrite_phy(o_dqldyn2d, d_ql_dyn2d)
2273
2274       CALL histwrite_phy(o_dqsdyn, d_qs_dyn)
2275
2276       CALL histwrite_phy(o_dqsdyn2d, d_qs_dyn2d)
2277
2278       IF (ok_bs) THEN
2279         CALL histwrite_phy(o_dqbsdyn, d_qbs_dyn)
2280         CALL histwrite_phy(o_dqbsdyn2d, d_qbs_dyn2d)
2281       ENDIF
2282
2283       CALL histwrite_phy(o_dudyn, d_u_dyn)
2284       CALL histwrite_phy(o_dvdyn, d_v_dyn)
2285
2286       IF (vars_defined) THEN
2287          zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys
2288       ENDIF
2289       CALL histwrite_phy(o_dtcon, zx_tmp_fi3d)
2290       IF (iflag_thermals.EQ.0) THEN
2291          IF (vars_defined) THEN
2292             zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
2293                  d_t_ajsb(1:klon,1:klev)/pdtphys
2294          ENDIF
2295          CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
2296       ELSE IF(iflag_thermals.GE.1.AND.iflag_wake.EQ.1) THEN
2297          IF (vars_defined) THEN
2298             zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
2299                  d_t_ajs(1:klon,1:klev)/pdtphys + &
2300                  d_t_wake(1:klon,1:klev)/pdtphys
2301          ENDIF
2302          CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
2303       ENDIF
2304       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_con(1:klon,1:klev)/pdtphys
2305       CALL histwrite_phy(o_ducon, zx_tmp_fi3d)
2306       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_con(1:klon,1:klev)/pdtphys
2307       CALL histwrite_phy(o_dvcon, zx_tmp_fi3d)
2308       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
2309       CALL histwrite_phy(o_dqcon, zx_tmp_fi3d)
2310       IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
2311       CALL histwrite_phy(o_dqcon2d, zx_tmp_fi2d)
2312
2313       IF (iflag_thermals.EQ.0) THEN
2314          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
2315          CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
2316       ELSE IF (iflag_thermals.GE.1.AND.iflag_wake.EQ.1) THEN
2317          IF (vars_defined) THEN
2318             zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys + &
2319                  d_q_ajs(1:klon,1:klev)/pdtphys + &
2320                  d_q_wake(1:klon,1:klev)/pdtphys
2321          ENDIF
2322          CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
2323       ENDIF
2324
2325       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lsc(1:klon,1:klev)/pdtphys
2326       CALL histwrite_phy(o_dtlsc, zx_tmp_fi3d)
2327       IF (vars_defined) zx_tmp_fi3d(1:klon, 1:klev)=(d_t_lsc(1:klon,1:klev)+d_t_eva(1:klon,1:klev))/pdtphys
2328       CALL histwrite_phy(o_dtlschr, zx_tmp_fi3d)
2329       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys
2330       CALL histwrite_phy(o_dqlsc, zx_tmp_fi3d)
2331       IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
2332       CALL histwrite_phy(o_dqlsc2d, zx_tmp_fi2d)
2333       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=beta_prec(1:klon,1:klev)
2334       CALL histwrite_phy(o_beta_prec, zx_tmp_fi3d)
2335!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2336       ! Sorties specifiques a la separation thermiques/non thermiques
2337       IF (iflag_thermals>=1) THEN
2338          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lscth(1:klon,1:klev)/pdtphys
2339          CALL histwrite_phy(o_dtlscth, zx_tmp_fi3d)
2340          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lscst(1:klon,1:klev)/pdtphys
2341          CALL histwrite_phy(o_dtlscst, zx_tmp_fi3d)
2342          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lscth(1:klon,1:klev)/pdtphys
2343          CALL histwrite_phy(o_dqlscth, zx_tmp_fi3d)
2344          IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
2345          CALL histwrite_phy(o_dqlscth2d, zx_tmp_fi2d)
2346          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lscst(1:klon,1:klev)/pdtphys
2347          CALL histwrite_phy(o_dqlscst, zx_tmp_fi3d)
2348          IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
2349          CALL histwrite_phy(o_dqlscst2d, zx_tmp_fi2d)
2350          CALL histwrite_phy(o_plulth, plul_th)
2351          CALL histwrite_phy(o_plulst, plul_st)
2352          IF (vars_defined) THEN
2353             DO i=1,klon
2354                zx_tmp_fi2d(1:klon)=lmax_th(:)
2355             ENDDO
2356          ENDIF
2357          CALL histwrite_phy(o_lmaxth, zx_tmp_fi2d)
2358          IF (vars_defined) THEN
2359             DO k=1,klev
2360                DO i=1,klon
2361                   IF (ptconvth(i,k)) THEN
2362                      zx_tmp_fi3d(i,k)=1.
2363                   ELSE
2364                      zx_tmp_fi3d(i,k)=0.
2365                   ENDIF
2366                ENDDO
2367             ENDDO
2368          ENDIF
2369          CALL histwrite_phy(o_ptconvth, zx_tmp_fi3d)
2370       ENDIF ! iflag_thermals>=1
2371!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2372       zpt_conv = 0.
2373       WHERE (ptconv) zpt_conv = 1.
2374       CALL histwrite_phy(o_ptconv, zpt_conv)
2375!!       IF (vars_defined)         zx_tmp_fi2d=float(itau_con)/float(itap)
2376!!       CALL histwrite_phy(o_ftime_con, zx_tmp_fi2d)
2377       IF (vars_defined) THEN
2378          zpt_conv2d(:) = 0.
2379          DO k=1,klev
2380            WHERE (ptconv(:,k)) zpt_conv2d(:) = 1.
2381          ENDDO
2382       ENDIF
2383       CALL histwrite_phy(o_ftime_deepcv, zpt_conv2d)
2384       IF (vars_defined) THEN
2385          zx_tmp_fi2d(:) = 0.
2386          DO k=1,klev
2387            WHERE (ptconvth(:,k)) zx_tmp_fi2d(:) = 1.
2388          ENDDO
2389       ENDIF
2390       CALL histwrite_phy(o_ftime_th, zx_tmp_fi2d)
2391       IF (vars_defined) THEN
2392           zx_tmp_fi2d(:) = max(zx_tmp_fi2d(:),zpt_conv2d(:))
2393       ENDIF
2394       CALL histwrite_phy(o_ftime_con, zx_tmp_fi2d)
2395!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2396       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_vdf(1:klon,1:klev)/pdtphys
2397       CALL histwrite_phy(o_dtvdf, zx_tmp_fi3d)
2398       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_diss(1:klon,1:klev)/pdtphys
2399       CALL histwrite_phy(o_dtdis, zx_tmp_fi3d)
2400       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_vdf(1:klon,1:klev)/pdtphys
2401       CALL histwrite_phy(o_dqvdf, zx_tmp_fi3d)
2402       IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
2403       CALL histwrite_phy(o_dqvdf2d, zx_tmp_fi2d)
2404       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_eva(1:klon,1:klev)/pdtphys
2405       CALL histwrite_phy(o_dteva, zx_tmp_fi3d)
2406       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_eva(1:klon,1:klev)/pdtphys
2407       CALL histwrite_phy(o_dqeva, zx_tmp_fi3d)
2408       IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
2409       CALL histwrite_phy(o_dqeva2d, zx_tmp_fi2d)
2410       CALL histwrite_phy(o_ratqs, ratqs)
2411       IF (vars_defined) THEN
2412          zx_tmp_fi3d(1:klon,1:klev)=d_t_ajs(1:klon,1:klev)/pdtphys - &
2413               d_t_ajsb(1:klon,1:klev)/pdtphys
2414       ENDIF
2415       CALL histwrite_phy(o_dtthe, zx_tmp_fi3d)
2416       IF (vars_defined) THEN
2417          zx_tmp_fi3d(1:klon,1:klev)=d_u_ajs(1:klon,1:klev)/pdtphys
2418       ENDIF
2419       CALL histwrite_phy(o_duthe, zx_tmp_fi3d)
2420       IF (vars_defined) THEN
2421          zx_tmp_fi3d(1:klon,1:klev)=d_v_ajs(1:klon,1:klev)/pdtphys
2422       ENDIF
2423       CALL histwrite_phy(o_dvthe, zx_tmp_fi3d)
2424
2425       IF (ok_bs) THEN
2426          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_qbs_vdf(1:klon,1:klev)/pdtphys
2427          CALL histwrite_phy(o_dqbsvdf, zx_tmp_fi3d)
2428          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_qbs_bsss(1:klon,1:klev)/pdtphys
2429          CALL histwrite_phy(o_dqbsbs, zx_tmp_fi3d)
2430          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_bsss(1:klon,1:klev)/pdtphys
2431          CALL histwrite_phy(o_dqbs, zx_tmp_fi3d)
2432          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_bsss(1:klon,1:klev)/pdtphys
2433          CALL histwrite_phy(o_dtbs, zx_tmp_fi3d)
2434       ENDIF
2435
2436       IF (iflag_thermals>=1) THEN
2437          ! Pour l instant 0 a y reflichir pour les thermiques
2438          ! regroupe avec ftime_deepcv et ftime_con
2439          !!zx_tmp_fi2d=0.
2440          !!CALL histwrite_phy(o_ftime_th, zx_tmp_fi2d)
2441          CALL histwrite_phy(o_f_th, fm_therm)
2442          CALL histwrite_phy(o_e_th, entr_therm)
2443          CALL histwrite_phy(o_w_th, zw2)
2444          CALL histwrite_phy(o_q_th, zqasc)
2445          CALL histwrite_phy(o_a_th, fraca)
2446          CALL histwrite_phy(o_cloudth_sth, cloudth_sth)
2447          CALL histwrite_phy(o_cloudth_senv, cloudth_senv)
2448          CALL histwrite_phy(o_cloudth_sigmath, cloudth_sigmath)
2449          CALL histwrite_phy(o_cloudth_sigmaenv, cloudth_sigmaenv)
2450          CALL histwrite_phy(o_d_th, detr_therm)
2451          CALL histwrite_phy(o_f0_th, f0)
2452          CALL histwrite_phy(o_zmax_th, zmax_th)
2453          IF (vars_defined) THEN
2454             zx_tmp_fi3d(1:klon,1:klev)=d_q_ajs(1:klon,1:klev)/pdtphys-d_q_ajsb(1:klon,1:klev)/pdtphys
2455          ENDIF
2456          CALL histwrite_phy(o_dqthe, zx_tmp_fi3d)
2457          IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
2458          CALL histwrite_phy(o_dqthe2d, zx_tmp_fi2d)
2459       ENDIF !iflag_thermals
2460       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_ajsb(1:klon,1:klev)/pdtphys
2461       CALL histwrite_phy(o_dtajs, zx_tmp_fi3d)
2462       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_ajsb(1:klon,1:klev)/pdtphys
2463       CALL histwrite_phy(o_dqajs, zx_tmp_fi3d)
2464       IF (vars_defined) CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
2465       CALL histwrite_phy(o_dqajs2d, zx_tmp_fi2d)
2466       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_swr(1:klon,1:klev)/pdtphys
2467       CALL histwrite_phy(o_dtswr, zx_tmp_fi3d)
2468       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_sw0(1:klon,1:klev)/pdtphys
2469       CALL histwrite_phy(o_dtsw0, zx_tmp_fi3d)
2470       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lwr(1:klon,1:klev)/pdtphys
2471       CALL histwrite_phy(o_dtlwr, zx_tmp_fi3d)
2472       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lw0(1:klon,1:klev)/pdtphys
2473       CALL histwrite_phy(o_dtlw0, zx_tmp_fi3d)
2474       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_ec(1:klon,1:klev)/pdtphys
2475       CALL histwrite_phy(o_dtec, zx_tmp_fi3d)
2476       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_vdf(1:klon,1:klev)/pdtphys
2477       CALL histwrite_phy(o_duvdf, zx_tmp_fi3d)
2478       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_vdf(1:klon,1:klev)/pdtphys
2479       CALL histwrite_phy(o_dvvdf, zx_tmp_fi3d)
2480       IF (ok_orodr) THEN
2481          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_oro(1:klon,1:klev)/pdtphys
2482          CALL histwrite_phy(o_duoro, zx_tmp_fi3d)
2483          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_oro(1:klon,1:klev)/pdtphys
2484          CALL histwrite_phy(o_dvoro, zx_tmp_fi3d)
2485          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_oro(1:klon,1:klev)/pdtphys
2486          CALL histwrite_phy(o_dtoro, zx_tmp_fi3d)
2487       ENDIF
2488       IF (ok_orolf) THEN
2489          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_lif(1:klon,1:klev)/pdtphys
2490          CALL histwrite_phy(o_dulif, zx_tmp_fi3d)
2491
2492          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_lif(1:klon,1:klev)/pdtphys
2493          CALL histwrite_phy(o_dvlif, zx_tmp_fi3d)
2494
2495          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lif(1:klon,1:klev)/pdtphys
2496          CALL histwrite_phy(o_dtlif, zx_tmp_fi3d)
2497       ENDIF
2498
2499       IF (ok_hines) THEN
2500          IF (vars_defined) zx_tmp_fi3d=du_gwd_hines/pdtphys
2501          CALL histwrite_phy(o_du_gwd_hines, zx_tmp_fi3d)
2502
2503          IF (vars_defined) zx_tmp_fi3d= dv_gwd_hines/pdtphys         
2504          CALL histwrite_phy(o_dv_gwd_hines, zx_tmp_fi3d)
2505         
2506          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_hin(1:klon,1:klev)/pdtphys
2507          CALL histwrite_phy(o_dthin, zx_tmp_fi3d)
2508          CALL histwrite_phy(o_ustr_gwd_hines, zustr_gwd_hines)
2509          CALL histwrite_phy(o_vstr_gwd_hines, zvstr_gwd_hines)
2510       ENDIF
2511
2512       IF (.not. ok_hines .and. ok_gwd_rando) THEN
2513          IF (vars_defined)  zx_tmp_fi3d=du_gwd_front / pdtphys
2514          CALL histwrite_phy(o_du_gwd_front, zx_tmp_fi3d)
2515         
2516          IF (vars_defined)  zx_tmp_fi3d=dv_gwd_front / pdtphys
2517          CALL histwrite_phy(o_dv_gwd_front, zx_tmp_fi3d)
2518         
2519          CALL histwrite_phy(o_ustr_gwd_front, zustr_gwd_front)
2520          CALL histwrite_phy(o_vstr_gwd_front, zvstr_gwd_front)
2521       ENDIF
2522
2523       IF (ok_gwd_rando) THEN
2524          IF (vars_defined)  zx_tmp_fi3d=du_gwd_rando / pdtphys
2525          CALL histwrite_phy(o_du_gwd_rando, zx_tmp_fi3d)
2526         
2527          IF (vars_defined)  zx_tmp_fi3d=dv_gwd_rando / pdtphys
2528          CALL histwrite_phy(o_dv_gwd_rando, zx_tmp_fi3d)
2529          CALL histwrite_phy(o_ustr_gwd_rando, zustr_gwd_rando)
2530          CALL histwrite_phy(o_vstr_gwd_rando, zvstr_gwd_rando)
2531          CALL histwrite_phy(o_east_gwstress, east_gwstress )
2532          CALL histwrite_phy(o_west_gwstress, west_gwstress )
2533       ENDIF
2534
2535       IF (ok_qch4) THEN
2536          IF (vars_defined) zx_tmp_fi3d=d_q_ch4
2537          CALL histwrite_phy(o_dqch4, zx_tmp_fi3d)
2538       ENDIF
2539       
2540       IF (vars_defined) THEN
2541         DO k=1, klevp1
2542           zx_tmp_fi3d1(:,k)=swup(:,k)*swradcorr(:)
2543         ENDDO
2544       ENDIF
2545       
2546       CALL histwrite_phy(o_rsu, zx_tmp_fi3d1)
2547
2548       IF (vars_defined) THEN
2549         DO k=1, klevp1
2550           zx_tmp_fi3d1(:,k)=swdn(:,k)*swradcorr(:)
2551         ENDDO
2552       ENDIF
2553       
2554       CALL histwrite_phy(o_rsd, zx_tmp_fi3d1)
2555
2556       IF (vars_defined) THEN
2557         DO k=1, klevp1
2558           zx_tmp_fi3d1(:,k)=swup0(:,k)*swradcorr(:)
2559         ENDDO
2560       ENDIF
2561       
2562       CALL histwrite_phy(o_rsucs, zx_tmp_fi3d1)
2563
2564       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
2565          IF (vars_defined) THEN
2566             DO k=1, klevp1
2567                zx_tmp_fi3d1(:,k)=swupc0(:,k)*swradcorr(:)
2568             ENDDO
2569          ENDIF
2570          CALL histwrite_phy(o_rsucsaf, zx_tmp_fi3d1)
2571       ENDIF
2572
2573       IF (vars_defined) THEN
2574         DO k=1, klevp1
2575           zx_tmp_fi3d1(:,k)=swdn0(:,k)*swradcorr(:)
2576         ENDDO
2577       ENDIF
2578       CALL histwrite_phy(o_rsdcs, zx_tmp_fi3d1)
2579
2580       IF (type_trac/='inca' .OR. config_inca=='aeNP') THEN
2581          IF (vars_defined) THEN
2582             DO k=1, klevp1
2583                zx_tmp_fi3d1(:,k)=swdnc0(:,k)*swradcorr(:)
2584             ENDDO
2585          ENDIF
2586          CALL histwrite_phy(o_rsdcsaf, zx_tmp_fi3d1)
2587       ENDIF
2588
2589       CALL histwrite_phy(o_rlu, lwup)
2590       CALL histwrite_phy(o_rld, lwdn)
2591       CALL histwrite_phy(o_rlucs, lwup0)
2592       CALL histwrite_phy(o_rldcs, lwdn0)
2593
2594       IF (vars_defined) THEN
2595          zx_tmp_fi3d(1:klon,1:klev)=d_t(1:klon,1:klev)+ &
2596               d_t_dyn(1:klon,1:klev)
2597       ENDIF
2598       CALL histwrite_phy(o_tnt, zx_tmp_fi3d)
2599
2600       IF (vars_defined) THEN
2601          zx_tmp_fi3d(1:klon,1:klev)=d_t_swr(1:klon,1:klev)/pdtphys + &
2602               d_t_lwr(1:klon,1:klev)/pdtphys
2603       ENDIF
2604       CALL histwrite_phy(o_tntr, zx_tmp_fi3d)
2605       IF (vars_defined) THEN
2606          zx_tmp_fi3d(1:klon,1:klev)= (d_t_lsc(1:klon,1:klev)+ &
2607               d_t_eva(1:klon,1:klev)+ &
2608               d_t_vdf(1:klon,1:klev))/pdtphys
2609       ENDIF
2610       CALL histwrite_phy(o_tntscpbl, zx_tmp_fi3d)
2611       IF (vars_defined) THEN
2612          zx_tmp_fi3d(1:klon,1:klev)=d_qx(1:klon,1:klev,ivap)+ &
2613               d_q_dyn(1:klon,1:klev)
2614       ENDIF
2615       CALL histwrite_phy(o_tnhus, zx_tmp_fi3d)
2616       IF (vars_defined) THEN
2617          zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys+ &
2618               d_q_eva(1:klon,1:klev)/pdtphys
2619       ENDIF
2620       CALL histwrite_phy(o_tnhusscpbl, zx_tmp_fi3d)
2621       CALL histwrite_phy(o_evu, coefm(:,:,is_ave))
2622       IF (vars_defined) THEN
2623          zx_tmp_fi3d(1:klon,1:klev)=q_seri(1:klon,1:klev)+ &
2624               ql_seri(1:klon,1:klev)
2625       ENDIF
2626       CALL histwrite_phy(o_h2o, zx_tmp_fi3d)
2627       IF (iflag_con >= 3) THEN
2628          IF (vars_defined) THEN
2629             zx_tmp_fi3d(1:klon,1:klev)=-1 * (dnwd(1:klon,1:klev)+ &
2630                  dnwd0(1:klon,1:klev))
2631          ENDIF
2632          CALL histwrite_phy(o_mcd, zx_tmp_fi3d)
2633          IF (vars_defined) THEN
2634             zx_tmp_fi3d(1:klon,1:klev)=upwd(1:klon,1:klev) + &
2635                  dnwd(1:klon,1:klev)+ dnwd0(1:klon,1:klev)
2636          ENDIF
2637          CALL histwrite_phy(o_dmc, zx_tmp_fi3d)
2638       ELSE IF (iflag_con == 2) THEN
2639          CALL histwrite_phy(o_mcd,  pmfd)
2640          IF (vars_defined) zx_tmp_fi3d = pmfu + pmfd
2641          CALL histwrite_phy(o_dmc,  zx_tmp_fi3d)
2642       ENDIF
2643       CALL histwrite_phy(o_ref_liq, ref_liq)
2644       CALL histwrite_phy(o_ref_ice, ref_ice)
2645!
2646       IF (ok_4xCO2atm) THEN
2647          IF (vars_defined) zx_tmp_fi2d(:) = swupp(:,klevp1)*swradcorr(:)
2648          CALL histwrite_phy(o_rsut4co2, zx_tmp_fi2d)
2649          IF (vars_defined) zx_tmp_fi2d(:) = lwupp(:,klevp1)
2650          CALL histwrite_phy(o_rlut4co2, zx_tmp_fi2d)
2651          IF (vars_defined) zx_tmp_fi2d(:) = swup0p(:,klevp1)*swradcorr(:)
2652          CALL histwrite_phy(o_rsutcs4co2, zx_tmp_fi2d)
2653          IF (vars_defined) zx_tmp_fi2d(:) = lwup0p(:,klevp1)
2654          CALL histwrite_phy(o_rlutcs4co2, zx_tmp_fi2d)
2655          IF (vars_defined) THEN
2656            DO k=1, klevp1
2657              zx_tmp_fi3d1(:,k)=swupp(:,k)*swradcorr(:)
2658            ENDDO
2659          ENDIF
2660          CALL histwrite_phy(o_rsu4co2, zx_tmp_fi3d1)
2661          IF (vars_defined) THEN
2662            DO k=1, klevp1
2663              zx_tmp_fi3d1(:,k)=swup0p(:,k)*swradcorr(:)
2664            ENDDO
2665          ENDIF
2666          CALL histwrite_phy(o_rsucs4co2, zx_tmp_fi3d1)
2667          IF (vars_defined) THEN
2668            DO k=1, klevp1
2669              zx_tmp_fi3d1(:,k)=swdnp(:,k)*swradcorr(:)
2670            ENDDO
2671          ENDIF
2672          CALL histwrite_phy(o_rsd4co2, zx_tmp_fi3d1)
2673          IF (vars_defined) THEN
2674            DO k=1, klevp1
2675              zx_tmp_fi3d1(:,k)=swdn0p(:,k)*swradcorr(:)
2676            ENDDO
2677          ENDIF
2678          CALL histwrite_phy(o_rsdcs4co2, zx_tmp_fi3d1)
2679          CALL histwrite_phy(o_rlu4co2, lwupp)
2680          CALL histwrite_phy(o_rlucs4co2, lwup0p)
2681          CALL histwrite_phy(o_rld4co2, lwdnp)
2682          CALL histwrite_phy(o_rldcs4co2, lwdn0p)
2683       ENDIF !ok_4xCO2atm
2684!!!!!!!!!!!! Sorties niveaux de pression NMC !!!!!!!!!!!!!!!!!!!!
2685       IF (.NOT. using_xios) THEN
2686         IF (.NOT.ok_all_xml) THEN
2687           ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
2688           ! Champs interpolles sur des niveaux de pression
2689           DO iff=7, nfiles-1 !--OB: here we deal with files 7,8,9
2690
2691             CALL histwrite_phy(o_tnondef,tnondef(:,:,iff-6),iff)
2692             CALL histwrite_phy(o_ta,twriteSTD(:,:,iff-6),iff)
2693             CALL histwrite_phy(o_zg,phiwriteSTD(:,:,iff-6),iff)
2694             CALL histwrite_phy(o_hus,qwriteSTD(:,:,iff-6),iff)
2695             CALL histwrite_phy(o_hur,rhwriteSTD(:,:,iff-6),iff)
2696             CALL histwrite_phy(o_ua,uwriteSTD(:,:,iff-6),iff)
2697             CALL histwrite_phy(o_va,vwriteSTD(:,:,iff-6),iff)
2698             CALL histwrite_phy(o_wap,wwriteSTD(:,:,iff-6),iff)
2699             IF (vars_defined) THEN
2700               DO k=1, nlevSTD
2701                  DO i=1, klon
2702                     IF (tnondef(i,k,iff-6).NE.missing_val) THEN
2703                       IF (freq_outNMC(iff-6).LT.0) THEN
2704                          freq_moyNMC(iff-6)=(mth_len*un_jour)/freq_calNMC(iff-6)
2705                       ELSE
2706                          freq_moyNMC(iff-6)=freq_outNMC(iff-6)/freq_calNMC(iff-6)
2707                       ENDIF
2708                       zx_tmp_fi3d_STD(i,k) = (100.*tnondef(i,k,iff-6))/freq_moyNMC(iff-6)
2709                     ELSE
2710                       zx_tmp_fi3d_STD(i,k) = missing_val
2711                     ENDIF
2712                  ENDDO
2713               ENDDO
2714             ENDIF
2715             CALL histwrite_phy(o_psbg,zx_tmp_fi3d_STD,iff)
2716             IF (vars_defined) THEN
2717               DO k=1, nlevSTD
2718                  DO i=1, klon
2719                    IF (O3sumSTD(i,k,iff-6).NE.missing_val) THEN
2720                       zx_tmp_fi3d_STD(i,k) = O3sumSTD(i,k,iff-6) * 1.e+9
2721                    ELSE
2722                       zx_tmp_fi3d_STD(i,k) = missing_val
2723                    ENDIF
2724                  ENDDO
2725               ENDDO !k=1, nlevSTD
2726             ENDIF
2727             CALL histwrite_phy(o_tro3,zx_tmp_fi3d_STD,iff)
2728             IF (read_climoz == 2) THEN
2729               IF (vars_defined) THEN
2730                 DO k=1, nlevSTD
2731                   DO i=1, klon
2732                      IF (O3daysumSTD(i,k,iff-6).NE.missing_val) THEN
2733                         zx_tmp_fi3d_STD(i,k) = O3daysumSTD(i,k,iff-6) * 1.e+9
2734                      ELSE
2735                         zx_tmp_fi3d_STD(i,k) = missing_val
2736                      ENDIF
2737                   ENDDO
2738                 ENDDO !k=1, nlevSTD
2739               ENDIF
2740               CALL histwrite_phy(o_tro3_daylight,zx_tmp_fi3d_STD,iff)
2741             ENDIF
2742             CALL histwrite_phy(o_uxv,uvsumSTD(:,:,iff-6),iff)
2743             CALL histwrite_phy(o_vxq,vqsumSTD(:,:,iff-6),iff)
2744             CALL histwrite_phy(o_vxT,vTsumSTD(:,:,iff-6),iff)
2745             CALL histwrite_phy(o_wxq,wqsumSTD(:,:,iff-6),iff)
2746             CALL histwrite_phy(o_vxphi,vphisumSTD(:,:,iff-6),iff)
2747             CALL histwrite_phy(o_wxT,wTsumSTD(:,:,iff-6),iff)
2748             CALL histwrite_phy(o_uxu,u2sumSTD(:,:,iff-6),iff)
2749             CALL histwrite_phy(o_vxv,v2sumSTD(:,:,iff-6),iff)
2750             CALL histwrite_phy(o_TxT,T2sumSTD(:,:,iff-6),iff)
2751           ENDDO !nfiles
2752         ENDIF
2753       ENDIF !.NOT. using_xios
2754
2755
2756       IF (using_xios) THEN
2757         IF (ok_all_xml) THEN
2758    !      DO iff=7, nfiles
2759
2760!         CALL histwrite_phy(o_tnondef,tnondef(:,:,3))
2761          CALL histwrite_phy(o_ta,tlevSTD(:,:))
2762          CALL histwrite_phy(o_zg,philevSTD(:,:))
2763          CALL histwrite_phy(o_hus,qlevSTD(:,:))
2764          CALL histwrite_phy(o_hur,rhlevSTD(:,:))
2765          CALL histwrite_phy(o_ua,ulevSTD(:,:))
2766          CALL histwrite_phy(o_va,vlevSTD(:,:))
2767          CALL histwrite_phy(o_wap,wlevSTD(:,:))
2768!         IF (vars_defined) THEN
2769!            DO k=1, nlevSTD
2770!               DO i=1, klon
2771!                  IF (tnondef(i,k,3).NE.missing_val) THEN
2772!                     IF (freq_outNMC(iff-6).LT.0) THEN
2773!                        freq_moyNMC(iff-6)=(mth_len*un_jour)/freq_calNMC(iff-6)
2774!                     ELSE
2775!                        freq_moyNMC(iff-6)=freq_outNMC(iff-6)/freq_calNMC(iff-6)
2776!                     ENDIF
2777!                     zx_tmp_fi3d_STD(i,k) = (100.*tnondef(i,k,3))/freq_moyNMC(iff-6)
2778!                  ELSE
2779!                     zx_tmp_fi3d_STD(i,k) = missing_val
2780!                  ENDIF
2781!               ENDDO
2782!            ENDDO
2783!         ENDIF
2784!         CALL histwrite_phy(o_psbg,zx_tmp_fi3d_STD)
2785          IF (vars_defined) THEN
2786             DO k=1, nlevSTD
2787                DO i=1, klon
2788                   IF (O3STD(i,k).NE.missing_val) THEN
2789                      zx_tmp_fi3d_STD(i,k) = O3STD(i,k) * 1.e+9
2790                   ELSE
2791                      zx_tmp_fi3d_STD(i,k) = missing_val
2792                   ENDIF
2793                ENDDO
2794             ENDDO !k=1, nlevSTD
2795          ENDIF
2796          CALL histwrite_phy(o_tro3,zx_tmp_fi3d_STD)
2797          IF (read_climoz == 2) THEN
2798             IF (vars_defined) THEN
2799                DO k=1, nlevSTD
2800                   DO i=1, klon
2801                      IF (O3daySTD(i,k).NE.missing_val) THEN
2802                         zx_tmp_fi3d_STD(i,k) = O3daySTD(i,k) * 1.e+9
2803                      ELSE
2804                         zx_tmp_fi3d_STD(i,k) = missing_val
2805                      ENDIF
2806                   ENDDO
2807                ENDDO !k=1, nlevSTD
2808             ENDIF
2809             CALL histwrite_phy(o_tro3_daylight,zx_tmp_fi3d_STD)
2810          ENDIF
2811          CALL histwrite_phy(o_uxv,uvSTD(:,:))
2812          CALL histwrite_phy(o_vxq,vqSTD(:,:))
2813          CALL histwrite_phy(o_vxT,vTSTD(:,:))
2814          CALL histwrite_phy(o_wxq,wqSTD(:,:))
2815          CALL histwrite_phy(o_vxphi,vphiSTD(:,:))
2816          CALL histwrite_phy(o_wxT,wTSTD(:,:))
2817          CALL histwrite_phy(o_uxu,u2STD(:,:))
2818          CALL histwrite_phy(o_vxv,v2STD(:,:))
2819          CALL histwrite_phy(o_TxT,T2STD(:,:))
2820!      ENDDO !nfiles
2821    ENDIF
2822  ENDIF !using_xios
2823!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2824       IF (iflag_phytrac == 1 ) then
2825!
2826         IF (type_trac == 'co2i') THEN
2827           itr = 0
2828           DO iq = 1, nqtot
2829             IF(.NOT.tracers(iq)%isInPhysics) CYCLE
2830             itr = itr + 1
2831!            write(*,*) 'phys_output_write_mod 2370: itr=',itr
2832             !--3D fields
2833             CALL histwrite_phy(o_trac(itr), tr_seri(:,:,itr))
2834             CALL histwrite_phy(o_dtr_vdf(itr),d_tr_cl(:,:,itr))
2835             CALL histwrite_phy(o_dtr_the(itr),d_tr_th(:,:,itr))
2836             CALL histwrite_phy(o_dtr_con(itr),d_tr_cv(:,:,itr))
2837             !--2D fields
2838             !--CO2 burden
2839             zx_tmp_fi2d=0.
2840             IF (vars_defined) THEN
2841                DO k=1,klev
2842                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,itr)
2843                ENDDO
2844             ENDIF
2845             CALL histwrite_phy(o_trac_cum(itr), zx_tmp_fi2d)
2846           ENDDO !--iq
2847           !--CO2 net fluxes
2848           CALL histwrite_phy(o_flx_co2_land,  fco2_land)
2849           CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean)
2850           CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor)
2851           CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor)
2852           CALL histwrite_phy(o_flx_co2_ff,    fco2_ff)
2853           CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
2854
2855         ELSE IF (type_trac == 'inco') THEN
2856           itr = 0
2857           DO iq = 1, nqtot
2858             IF(.NOT.tracers(iq)%isInPhysics) CYCLE
2859             itr = itr+1
2860             IF(tracers(iq)%component /= 'co2i') CYCLE
2861             !--3D fields
2862             CALL histwrite_phy(o_trac   (itr),tr_seri(:,:,itr))
2863             CALL histwrite_phy(o_dtr_vdf(itr),d_tr_cl(:,:,itr))
2864             CALL histwrite_phy(o_dtr_the(itr),d_tr_th(:,:,itr))
2865             CALL histwrite_phy(o_dtr_con(itr),d_tr_cv(:,:,itr))
2866             !--2D fields
2867             !--CO2 burden
2868             zx_tmp_fi2d=0.
2869             IF (vars_defined) THEN
2870                DO k=1,klev
2871                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,itr)
2872                ENDDO
2873             ENDIF
2874             CALL histwrite_phy(o_trac_cum(itr), zx_tmp_fi2d)
2875           ENDDO !--iq
2876           !--CO2 net fluxes
2877           CALL histwrite_phy(o_flx_co2_land,  fco2_land)
2878           CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean)
2879           CALL histwrite_phy(o_flx_co2_ocean_cor, fco2_ocean_cor)
2880           CALL histwrite_phy(o_flx_co2_land_cor, fco2_land_cor)
2881           CALL histwrite_phy(o_flx_co2_ff,    fco2_ff)
2882           CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
2883
2884         ELSE IF (ANY(type_trac==['lmdz','coag'])) THEN
2885           itr = 0
2886           DO iq = 1, nqtot
2887             IF(.NOT.tracers(iq)%isInPhysics) CYCLE
2888             itr = itr + 1
2889!            write(*,*) 'phys_output_write_mod 2337: itr=',itr
2890             !--3D fields
2891             CALL histwrite_phy(o_trac(itr), tr_seri(:,:,itr))
2892             CALL histwrite_phy(o_dtr_vdf(itr),d_tr_cl(:,:,itr))
2893             CALL histwrite_phy(o_dtr_the(itr),d_tr_th(:,:,itr))
2894             CALL histwrite_phy(o_dtr_con(itr),d_tr_cv(:,:,itr))
2895             CALL histwrite_phy(o_dtr_lessi_impa(itr),d_tr_lessi_impa(:,:,itr))
2896             CALL histwrite_phy(o_dtr_lessi_nucl(itr),d_tr_lessi_nucl(:,:,itr))
2897             CALL histwrite_phy(o_dtr_insc(itr),d_tr_insc(:,:,itr))
2898             CALL histwrite_phy(o_dtr_bcscav(itr),d_tr_bcscav(:,:,itr))
2899             CALL histwrite_phy(o_dtr_evapls(itr),d_tr_evapls(:,:,itr))
2900             CALL histwrite_phy(o_dtr_ls(itr),d_tr_ls(:,:,itr))
2901             CALL histwrite_phy(o_dtr_trsp(itr),d_tr_trsp(:,:,itr))
2902             CALL histwrite_phy(o_dtr_sscav(itr),d_tr_sscav(:,:,itr))
2903             CALL histwrite_phy(o_dtr_sat(itr),d_tr_sat(:,:,itr))
2904             CALL histwrite_phy(o_dtr_uscav(itr),d_tr_uscav(:,:,itr))
2905            !--2D fields
2906             CALL histwrite_phy(o_dtr_wet_con(itr), flux_tr_wet(:,itr))
2907             CALL histwrite_phy(o_dtr_dry(itr), flux_tr_dry(:,itr))
2908             zx_tmp_fi2d=0.
2909             IF (vars_defined) THEN
2910                DO k=1,klev
2911                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,itr)
2912                ENDDO
2913             ENDIF
2914             CALL histwrite_phy(o_trac_cum(itr), zx_tmp_fi2d)
2915           ENDDO !--iq
2916         ENDIF   !--type_trac
2917       ENDIF   !(iflag_phytrac==1)
2918
2919       if (activate_ocean_skin >= 1) then
2920          CALL histwrite_phy(o_delta_sst, delta_sst)
2921          CALL histwrite_phy(o_delta_sal, delta_sal)
2922          CALL histwrite_phy(o_ds_ns, ds_ns)
2923          CALL histwrite_phy(o_dt_ns, dt_ns)
2924          CALL histwrite_phy(o_dter, dter)
2925          CALL histwrite_phy(o_dser, dser)
2926          CALL histwrite_phy(o_tkt, tkt)
2927          CALL histwrite_phy(o_tks, tks)
2928          CALL histwrite_phy(o_taur, taur)
2929          CALL histwrite_phy(o_sss, sss)
2930       end if
2931
2932    !! runoff land bucket - ajout S. Nguyen 23 07 2024
2933    CALL histwrite_phy(o_runoff_diag, runoff_diag)
2934
2935#ifdef ISO
2936    !write(*,*) 'tmp phys_output_write: ntiso=',ntiso
2937
2938    DO ixt = 1, ntiso
2939        !write(*,*) 'ixt,o_xtovap(ixt)=',ixt,o_xtovap(ixt)
2940        IF (vars_defined) zx_tmp_fi2d(:) = xtrain_fall(ixt,:) + xtsnow_fall(ixt,:)
2941        CALL histwrite_phy(o_xtprecip(ixt), zx_tmp_fi2d)
2942
2943        IF (vars_defined) zx_tmp_fi2d(:) = xtrain_lsc(ixt,:) + xtsnow_lsc(ixt,:)
2944        CALL histwrite_phy(o_xtplul(ixt), zx_tmp_fi2d)
2945
2946        IF (vars_defined) zx_tmp_fi2d(:) = xtrain_con(ixt,:) + xtsnow_con(ixt,:)
2947        CALL histwrite_phy(o_xtpluc(ixt), zx_tmp_fi2d)
2948        CALL histwrite_phy(o_xtevap(ixt),   xtevap(ixt,:))
2949        CALL histwrite_phy(o_xtovap(ixt),  xt_seri(ixt,:,:))
2950        CALL histwrite_phy(o_xtoliq(ixt), xtl_seri(ixt,:,:))
2951
2952        !! runoff land bucket - ajout S. Nguyen 25 avril 2024
2953        CALL histwrite_phy(o_xtrunoff_diag(ixt), xtrunoff_diag(ixt,:))
2954
2955
2956        DO nsrf = 1, nbsrf ! ajout Camille 8 mai 2023
2957        IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fxtevap(ixt,:, nsrf)
2958        CALL histwrite_phy(o_xtevap_srf(ixt,nsrf), zx_tmp_fi2d)
2959        ENDDO
2960
2961        IF (vars_defined) zx_tmp_fi3d(:,:)=xtl_seri(ixt,:,:)+xts_seri(ixt,:,:)
2962        CALL histwrite_phy(o_xtcond(ixt), zx_tmp_fi3d)
2963        CALL histwrite_phy(o_dxtdyn(ixt),   d_xt_dyn(ixt,:,:))
2964        CALL histwrite_phy(o_dxtldyn(ixt), d_xtl_dyn(ixt,:,:))
2965
2966        IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_con(ixt,:,:)/pdtphys
2967        CALL histwrite_phy(o_dxtcon(ixt), zx_tmp_fi3d)
2968
2969        IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_lsc(ixt,:,:)/pdtphys
2970        CALL histwrite_phy(o_dxtlsc(ixt), zx_tmp_fi3d)
2971
2972        IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_eva(ixt,:,:)/pdtphys
2973        CALL histwrite_phy(o_dxteva(ixt), zx_tmp_fi3d)
2974
2975        IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_vdf(ixt,:,:)/pdtphys
2976        CALL histwrite_phy(o_dxtvdf(ixt), zx_tmp_fi3d)
2977
2978        IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_ajsb(ixt,:,:)/pdtphys
2979        CALL histwrite_phy(o_dxtajs(ixt), zx_tmp_fi3d)
2980
2981        IF (vars_defined) zx_tmp_fi3d(:,:)=(d_xt_ajs(ixt,:,:)-d_xt_ajsb(ixt,:,:))/pdtphys
2982        CALL histwrite_phy(o_dxtthe(ixt), zx_tmp_fi3d)
2983
2984        IF (ok_qch4) THEN
2985          IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_ch4(ixt,:,:)/pdtphys
2986          CALL histwrite_phy(o_dxtch4(ixt), zx_tmp_fi3d)
2987        ENDIF
2988
2989        IF (ixt == iso_HTO) THEN
2990          IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_prod_nucl(ixt,:,:)/pdtphys
2991          CALL histwrite_phy(o_dxtprod_nucl(ixt), zx_tmp_fi3d)
2992
2993          IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_cosmo(ixt,:,:)/pdtphys
2994          CALL histwrite_phy(o_dxtcosmo(ixt), zx_tmp_fi3d)
2995
2996          IF (vars_defined) zx_tmp_fi3d(:,:)=d_xt_decroiss(ixt,:,:)/pdtphys
2997          CALL histwrite_phy(o_dxtdecroiss(ixt), zx_tmp_fi3d)
2998        ENDIF
2999
3000    !write(*,*) 'phys_output_write_mod 2531'
3001    ENDDO
3002#endif
3003
3004       IF (.NOT.vars_defined) THEN
3005          !$OMP MASTER
3006#ifndef CPP_IOIPSL_NO_OUTPUT
3007          DO iff=1,nfiles
3008             IF (clef_files(iff)) THEN
3009                CALL histend(nid_files(iff))
3010                ndex2d = 0
3011                ndex3d = 0
3012             ENDIF ! clef_files
3013          ENDDO !  iff
3014#endif
3015
3016!SN activate water isotopes present in tracer.def
3017#ifdef ISO
3018          DO ixt = 1, ntiso
3019            outiso = TRIM(isoName(ixt))
3020            i = INDEX(outiso, '_', .TRUE.)
3021            outiso = outiso(1:i-1)//outiso(i+1:LEN_TRIM(outiso))
3022
3023            CALL xios_set_fieldgroup_attr("iso2D_"//TRIM(outiso), enabled=.TRUE.)
3024            CALL xios_set_fieldgroup_attr("iso3D_"//TRIM(outiso), enabled=.TRUE.)
3025
3026          ENDDO
3027#endif
3028          !On finalise l'initialisation:
3029          IF (using_xios) CALL wxios_closedef()
3030
3031          !$OMP END MASTER
3032          !$OMP BARRIER
3033          vars_defined = .TRUE.
3034
3035       ENDIF !--.NOT.vars_defined
3036
3037    ENDDO
3038
3039    IF (vars_defined) THEN
3040       ! On synchronise les fichiers pour IOIPSL
3041#ifndef CPP_IOIPSL_NO_OUTPUT
3042       !$OMP MASTER
3043       DO iff=1,nfiles
3044          IF (ok_sync .AND. clef_files(iff)) THEN
3045             CALL histsync(nid_files(iff))
3046          ENDIF
3047       ENDDO
3048       !$OMP END MASTER
3049#endif
3050    ENDIF
3051
3052  END SUBROUTINE phys_output_write
3053
3054END MODULE phys_output_write_mod
Note: See TracBrowser for help on using the repository browser.