source: LMDZ6/branches/IPSLCM6.0.15/libf/phylmd/phys_output_write_mod.F90 @ 3400

Last change on this file since 3400 was 3400, checked in by Laurent Fairhead, 6 years ago

Due to a difficult to correct bug, near surface fields can take abnormal values in very specific circumstances.
While waiting to find a correction, these modifications will force the values of these fields within reasonable bounds.
To get back to the previous behaviour of the model, use iflag_bug_t2m_ipslcm61 = 1 (it is 0 by default)

  • 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: 91.2 KB
Line 
1!
2! $Id: phys_output_write_mod.F90 3400 2018-10-01 11:33:32Z fairhead $
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_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, ivap, iliq, isol, new_aod, ok_sync, &
20       ptconv, read_climoz, clevSTD, ptconvth, &
21       d_u, d_t, qx, d_qx, zmasse, flag_aerosol, flag_aerosol_strat, ok_cdnc)
22
23    ! This subroutine does the actual writing of diagnostics that were
24    ! defined and initialised in phys_output_mod.F90
25
26    USE dimphy, ONLY: klon, klev, klevp1
27    USE infotrac_phy, ONLY: nbtr
28    USE mod_phys_lmdz_para, ONLY: is_north_pole_phy,is_south_pole_phy
29    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
30    USE time_phylmdz_mod, ONLY: day_step_phy, start_time, itau_phy
31    USE vertical_layers_mod, ONLY : ap, bp, aps, bps
32    USE phys_output_ctrlout_mod, ONLY: o_phis, o_aire, is_ter, is_lic, is_oce, &
33         o_longitude, o_latitude, &
34         o_Ahyb, o_Bhyb,o_Ahyb_bounds, o_Bhyb_bounds, &
35         o_Ahyb_mid, o_Bhyb_mid,o_Ahyb_mid_bounds, o_Bhyb_mid_bounds, &
36         is_ave, is_sic, o_contfracATM, o_contfracOR, &
37         o_aireTER, o_flat, o_slp, o_ptstar, o_pt0, o_tsol, &
38         o_t2m, o_t2m_min, o_t2m_max, &
39         o_t2m_min_mon, o_t2m_max_mon, &
40         o_q2m, o_ustar, o_u10m, o_v10m, &
41         o_wind10m, o_wind10max, o_gusts, o_sicf, &
42         o_psol, o_mass, o_qsurf, o_qsol, &
43         o_precip, o_rain_fall, o_rain_con, o_ndayrain, o_plul, o_pluc, o_plun, &
44         o_snow, o_msnow, o_fsnow, o_evap, o_ep,o_epmax_diag, & ! epmax_cape
45         o_tops, o_tops0, o_topl, o_topl0, &
46         o_SWupTOA, o_SWupTOAclr, o_SWupTOAcleanclr, o_SWdnTOA, &
47         o_SWdnTOAclr, o_nettop, o_SWup200, &
48         o_SWup200clr, o_SWdn200, o_SWdn200clr, &
49         o_LWup200, o_LWup200clr, o_LWdn200, &
50         o_LWdn200clr, o_sols, o_sols0, &
51         o_soll, o_radsol, o_soll0, o_SWupSFC, &
52         o_SWupSFCclr, o_SWupSFCcleanclr, o_SWdnSFC, o_SWdnSFCclr, o_SWdnSFCcleanclr, &
53         o_LWupSFC, o_LWdnSFC, o_LWupSFCclr, &
54         o_LWdnSFCclr, o_LWupTOAcleanclr, o_LWdnSFCcleanclr, o_bils, o_bils_diss, &
55         o_bils_ec,o_bils_ech, o_bils_tke, o_bils_kinetic, &
56         o_bils_latent, o_bils_enthalp, o_sens, &
57         o_fder, o_ffonte, o_fqcalving, o_fqfonte, o_mrroli, o_runofflic, &
58         o_taux, o_tauy, o_snowsrf, o_qsnow, &
59         o_snowhgt, o_toice, o_sissnow, o_runoff, &
60         o_albslw3, o_pourc_srf, o_fract_srf, &
61         o_taux_srf, o_tauy_srf, o_tsol_srf, &
62         o_evappot_srf, o_ustar_srf, o_u10m_srf, &
63         o_v10m_srf, o_t2m_srf, o_evap_srf, &
64         o_sens_srf, o_lat_srf, o_flw_srf, &
65         o_fsw_srf, o_wbils_srf, o_wbilo_srf, &
66         o_wevap_srf, o_wrain_srf, o_wsnow_srf, &
67         o_tke_srf, o_tke_max_srf,o_dltpbltke_srf, o_wstar, &
68         o_l_mixmin,o_l_mix, &
69         o_cdrm, o_cdrh, o_cldl, o_cldm, o_cldh, &
70         o_cldt, o_JrNt, o_cldljn, o_cldmjn, &
71         o_cldhjn, o_cldtjn, o_cldq, o_lwp, o_iwp, &
72         o_ue, o_ve, o_uq, o_vq, o_cape, o_pbase, &
73         o_uwat, o_vwat, &
74         o_ptop, o_fbase, o_plcl, o_plfc, &
75         o_wbeff, o_convoccur, o_cape_max, o_upwd, o_ep,o_epmax_diag, o_Ma, &
76         o_dnwd, o_dnwd0, o_ftime_deepcv, o_ftime_con, o_mc, &
77         o_prw, o_prlw, o_prsw, o_s_pblh, o_s_pblt, o_s_lcl, &
78         o_s_therm, o_uSTDlevs, o_vSTDlevs, &
79         o_wSTDlevs, o_zSTDlevs, o_qSTDlevs, &
80         o_tSTDlevs, epsfra, o_t_oce_sic, &
81         o_ale_bl, o_alp_bl, o_ale_wk, o_alp_wk, &
82         o_dtvdf_x    , o_dtvdf_w    , o_dqvdf_x    , o_dqvdf_w    , &
83         o_sens_x     , o_sens_w     , o_flat_x     , o_flat_w     , &
84         o_delta_tsurf, &
85         o_cdragh_x   , o_cdragh_w   , o_cdragm_x   , o_cdragm_w   , &
86         o_kh         , o_kh_x       , o_kh_w       , &
87         o_ale, o_alp, o_cin, o_WAPE, o_wake_h, &
88         o_wake_s, o_wake_deltat, o_wake_deltaq, &
89         o_wake_omg, o_dtwak, o_dqwak, o_dqwak2d, o_Vprecip, &
90         o_ftd, o_fqd, o_wdtrainA, o_wdtrainM, &
91         o_n2, o_s2, o_proba_notrig, &
92         o_random_notrig, o_ale_bl_stat, &
93         o_ale_bl_trig, o_alp_bl_det, &
94         o_alp_bl_fluct_m, o_alp_bl_fluct_tke, &
95         o_alp_bl_conv, o_alp_bl_stat, &
96         o_slab_qflux, o_tslab, o_slab_bils, &
97         o_slab_bilg, o_slab_sic, o_slab_tice, &
98         o_slab_hdiff, o_slab_ekman, o_slab_gm,  &
99         o_weakinv, o_dthmin, o_cldtau, &
100         o_cldemi, o_pr_con_l, o_pr_con_i, &
101         o_pr_lsc_l, o_pr_lsc_i, o_re, o_fl, &
102         o_rh2m, &
103         o_qsat2m, o_tpot, o_tpote, o_SWnetOR, &
104         o_SWdownOR, o_LWdownOR, o_snowl, &
105         o_solldown, o_dtsvdfo, o_dtsvdft, &
106         o_dtsvdfg, o_dtsvdfi, o_z0m, o_z0h,  o_od443aer, o_od550aer, &
107         o_dryod550aer, o_od865aer, o_abs550aer, o_od550lt1aer, &
108         o_sconcso4, o_sconcno3, o_sconcoa, o_sconcbc, &
109         o_sconcss, o_sconcdust, o_concso4, o_concno3, &
110         o_concoa, o_concbc, o_concss, o_concdust, &
111         o_loadso4, o_loadoa, o_loadbc, o_loadss, &
112         o_loaddust, o_loadno3, o_tausumaero, &
113         o_drytausumaero, o_tausumaero_lw, &
114         o_topswad, o_topswad0, o_solswad, o_solswad0, &
115         o_toplwad, o_toplwad0, o_sollwad, o_sollwad0, &
116         o_swtoaas_nat, o_swsrfas_nat, &
117         o_swtoacs_nat, o_swtoaas_ant, &
118         o_swsrfas_ant, o_swtoacs_ant, &
119         o_swsrfcs_ant, o_swtoacf_nat, &
120         o_swsrfcf_nat, o_swtoacf_ant, &
121         o_swsrfcs_nat, o_swsrfcf_ant, &
122         o_swtoacf_zero, o_swsrfcf_zero, &
123         o_topswai, o_solswai, o_toplwai, o_sollwai, o_scdnc, &
124         o_cldncl, o_reffclws, o_reffclwc, o_solbnd, o_stratomask,&
125         o_cldnvi, o_lcc, o_lcc3d, o_lcc3dcon, &
126         o_lcc3dstra, o_icc3dcon, o_icc3dstra, &
127         o_cldicemxrat, o_cldwatmxrat, o_reffclwtop, o_ec550aer, &
128         o_lwcon, o_iwcon, o_temp, o_theta, &
129         o_ovapinit, o_ovap, o_oliq, o_ocond, o_geop, &
130         o_vitu, o_vitv, o_vitw, o_pres, o_paprs, &
131         o_zfull, o_zhalf, o_rneb, o_rnebjn, o_rnebcon, &
132         o_rnebls, o_rneblsvol, o_rhum, o_ozone, o_ozone_light, &
133         o_duphy, o_dtphy, o_dqphy, o_dqphy2d, o_dqlphy, o_dqlphy2d, &
134         o_dqsphy, o_dqsphy2d, o_albe_srf, o_z0m_srf, o_z0h_srf, &
135         o_ages_srf, o_snow_srf, o_alb1, o_alb2, o_tke, &
136         o_tke_max, o_kz, o_kz_max, o_clwcon, &
137         o_dtdyn, o_dqdyn, o_dqdyn2d, o_dqldyn, o_dqldyn2d, &
138         o_dqsdyn, o_dqsdyn2d, o_dudyn, o_dvdyn, &
139         o_dtcon, o_tntc, o_ducon, o_dvcon, &
140         o_dqcon, o_dqcon2d, o_tnhusc, o_tnhusc, o_dtlsc, &
141         o_dtlschr, o_dqlsc, o_dqlsc2d, o_beta_prec, &
142         o_dtlscth, o_dtlscst, o_dqlscth, o_dqlscth2d, &
143         o_dqlscst, o_dqlscst2d, o_plulth, o_plulst, &
144         o_ptconvth, o_lmaxth, o_dtvdf, &
145         o_dtdis, o_dqvdf, o_dqvdf2d, o_dteva, o_dqeva, o_dqeva2d, &
146         o_ptconv, o_ratqs, o_dtthe, &
147         o_duthe, o_dvthe, o_ftime_th, &
148         o_f_th, o_e_th, o_w_th, o_q_th, &
149         o_a_th, o_cloudth_sth, o_cloudth_senv, &
150         o_cloudth_sigmath, o_cloudth_sigmaenv, &
151         o_d_th, o_f0_th, o_zmax_th, &
152         o_dqthe, o_dqthe2d, o_dtajs, o_dqajs, o_dqajs2d, o_dtswr, &
153         o_dtsw0, o_dtlwr, o_dtlw0, o_dtec, &
154         o_duvdf, o_dvvdf, o_duoro, o_dvoro, &
155         o_dtoro, o_dulif, o_dvlif, o_dtlif, &
156         o_du_gwd_hines, o_dv_gwd_hines, o_dthin, o_dqch4, o_rsu, &
157         o_du_gwd_front, o_dv_gwd_front, &
158         o_east_gwstress, o_west_gwstress, &
159         o_rsd, o_rlu, o_rld, o_rsucs, o_rsdcs, o_rsucsaf, o_rsdcsaf, &
160         o_rlucs, o_rldcs, o_tnt, o_tntr, &
161         o_tntscpbl, o_tnhus, o_tnhusscpbl, &
162         o_evu, o_h2o, o_mcd, o_dmc, o_ref_liq, &
163         o_ref_ice, o_rsut4co2, o_rlut4co2, &
164         o_rsutcs4co2, o_rlutcs4co2, o_rsu4co2, &
165         o_rlu4co2, o_rsucs4co2, o_rlucs4co2, &
166         o_rsd4co2, o_rld4co2, o_rsdcs4co2, &
167         o_rldcs4co2, o_tnondef, o_ta, o_zg, &
168         o_hus, o_hur, o_ua, o_va, o_wap, &
169         o_psbg, o_tro3, o_tro3_daylight, &
170         o_uxv, o_vxq, o_vxT, o_wxq, o_vxphi, &
171         o_wxT, o_uxu, o_vxv, o_TxT, o_trac, &
172#ifdef REPROBUS
173         o_nas, &
174#endif
175         o_dtr_vdf, o_dtr_the, o_dtr_con, &
176         o_dtr_lessi_impa, o_dtr_lessi_nucl, &
177         o_dtr_insc, o_dtr_bcscav, o_dtr_evapls, &
178         o_dtr_ls, o_dtr_trsp, o_dtr_sscav, o_dtr_dry, &
179         o_dtr_sat, o_dtr_uscav, o_trac_cum, o_du_gwd_rando, o_dv_gwd_rando, &
180         o_ustr_gwd_hines,o_vstr_gwd_hines,o_ustr_gwd_rando,o_vstr_gwd_rando, &
181         o_ustr_gwd_front,o_vstr_gwd_front, &
182         o_sens_prec_liq_oce, o_sens_prec_liq_sic, &
183         o_sens_prec_sol_oce, o_sens_prec_sol_sic, &
184         o_lat_prec_liq_oce, o_lat_prec_liq_sic, &
185         o_lat_prec_sol_oce, o_lat_prec_sol_sic, &
186         o_sza, &
187! Marine
188         o_map_prop_hc, o_map_prop_hist, o_map_emis_hc, o_map_iwp_hc, &
189         o_map_deltaz_hc, o_map_pcld_hc, o_map_tcld_hc, &
190         o_map_emis_hist, o_map_iwp_hist, o_map_deltaz_hist, &
191         o_map_rad_hist, &
192         o_map_emis_Cb, o_map_pcld_Cb, o_map_tcld_Cb, &
193         o_map_emis_ThCi, o_map_pcld_ThCi, o_map_tcld_ThCi, &
194         o_map_emis_Anv, o_map_pcld_Anv, o_map_tcld_Anv, &
195         o_map_ntot, o_map_hc,o_map_hist,o_map_Cb,o_map_ThCi,o_map_Anv, &
196         o_alt_tropo, &
197! Tropopause
198         o_p_tropopause, o_z_tropopause, o_t_tropopause,  &
199         o_col_O3_strato, o_col_O3_tropo               ! Added ThL
200
201
202#ifdef CPP_StratAer
203    USE phys_output_ctrlout_mod, ONLY:  &
204         o_budg_3D_nucl, o_budg_3D_cond_evap, o_budg_3D_ocs_to_so2, o_budg_3D_so2_to_h2so4, &
205         o_budg_sed_part, o_R2SO4, o_OCS_lifetime, o_SO2_lifetime, &
206         o_budg_3D_backgr_ocs, o_budg_3D_backgr_so2, &
207         o_budg_dep_dry_ocs, o_budg_dep_wet_ocs, &
208         o_budg_dep_dry_so2, o_budg_dep_wet_so2, &
209         o_budg_dep_dry_h2so4, o_budg_dep_wet_h2so4, &
210         o_budg_dep_dry_part, o_budg_dep_wet_part, &
211         o_budg_emi_ocs, o_budg_emi_so2, o_budg_emi_h2so4, o_budg_emi_part, &
212         o_budg_ocs_to_so2, o_budg_so2_to_h2so4, o_budg_h2so4_to_part, &
213         o_surf_PM25_sulf, o_ext_strat_550, o_tau_strat_550, &
214         o_vsed_aer, o_tau_strat_1020, o_ext_strat_1020, o_f_r_wet
215#endif
216
217    USE phys_state_var_mod, ONLY: pctsrf, rain_fall, snow_fall, &
218         qsol, z0m, z0h, fevap, agesno, &
219         nday_rain, rain_con, snow_con, &
220         topsw, toplw, toplw0, swup, swdn, &
221         topsw0, swupc0, swdnc0, swup0, swdn0, SWup200, SWup200clr, &
222         SWdn200, SWdn200clr, LWup200, LWup200clr, &
223         LWdn200, LWdn200clr, solsw, solsw0, sollw, &
224         radsol, swradcorr, sollw0, sollwdown, sollw, gustiness, &
225         sollwdownclr, lwdnc0, lwdn0, ftsol, ustar, u10m, &
226         v10m, pbl_tke, wake_delta_pbl_TKE, &
227         delta_tsurf, &
228         wstar, cape, ema_pcb, ema_pct, &
229         ema_cbmf, Ma, fm_therm, ale_bl, alp_bl, ale, &
230         alp, cin, wake_pe, wake_s, wake_deltat, &
231         wake_deltaq, ftd, fqd, ale_bl_trig, albsol1, &
232         ale_wake, ale_bl_stat, &
233         rnebcon, wo, falb1, albsol2, coefh, clwcon0, &
234         ratqs, entr_therm, zqasc, detr_therm, f0, &
235         lwup, lwdn, lwupc0, lwup0, coefm, &
236         swupp, lwupp, swupc0p, swup0p, lwupc0p, lwup0p, swdnp, lwdnp, &
237         swdnc0p, swdn0p, lwdnc0p, lwdn0p, tnondef, O3sumSTD, uvsumSTD, &
238         vqsumSTD, vTsumSTD, O3daysumSTD, wqsumSTD, &
239         vphisumSTD, wTsumSTD, u2sumSTD, v2sumSTD, &
240         T2sumSTD, nlevSTD, du_gwd_rando, du_gwd_front, &
241         ulevSTD, vlevSTD, wlevSTD, philevSTD, qlevSTD, tlevSTD, &
242         rhlevSTD, O3STD, O3daySTD, uvSTD, vqSTD, vTSTD, wqSTD, &
243         vphiSTD, wTSTD, u2STD, v2STD, T2STD, missing_val_nf90
244
245    USE phys_local_var_mod, ONLY: zxfluxlat, slp, ptstar, pt0, zxtsol, zt2m, &
246         zt2m_cor,zq2m_cor,zu10m_cor,zv10m_cor, &
247         t2m_min_mon, t2m_max_mon, evap, &
248         l_mixmin,l_mix, &
249         zu10m, zv10m, zq2m, zustar, zxqsurf, &
250         rain_lsc, rain_num, snow_lsc, bils, sens, fder, &
251         zxffonte, zxfqcalving, zxfqfonte, zxrunofflic, fluxu, &
252         fluxv, zxsnow, qsnow, snowhgt, to_ice, &
253         sissnow, runoff, albsol3_lic, evap_pot, &
254         t2m, fluxt, fluxlat, fsollw, fsolsw, &
255         wfbils, wfbilo, wfevap, wfrain, wfsnow, &
256         cdragm, cdragh, cldl, cldm, &
257         cldh, cldt, JrNt, cldljn, cldmjn, cldhjn, &
258         cldtjn, cldq, flwp, fiwp, ue, ve, uq, vq, &
259         uwat, vwat, &
260         plcl, plfc, wbeff, convoccur, upwd, dnwd, dnwd0, prw, prlw, prsw, &
261         s_pblh, s_pblt, s_lcl, s_therm, uwriteSTD, &
262         vwriteSTD, wwriteSTD, phiwriteSTD, qwriteSTD, &
263         twriteSTD, alp_wake, &
264         dtvdf_x    ,dtvdf_w    ,dqvdf_x    ,dqvdf_w    , &
265         sens_x     ,sens_w     ,zxfluxlat_x,zxfluxlat_w, &
266         cdragh_x   ,cdragh_w   ,cdragm_x   ,cdragm_w   , &
267         kh         ,kh_x       ,kh_w       , &
268         wake_h, &
269         wake_omg, d_t_wake, d_q_wake, Vprecip, &
270         wdtrainA, wdtrainM, n2, s2, proba_notrig, &
271         random_notrig, &
272         alp_bl_det, alp_bl_fluct_m, alp_bl_conv, &
273         alp_bl_stat, alp_bl_fluct_tke, slab_wfbils, &
274         weak_inversion, dthmin, cldtau, cldemi, &
275         pmflxr, pmflxs, prfl, psfl, re, fl, rh2m, &
276         qsat2m, tpote, tpot, d_ts, od443aer, od550aer, dryod550aer, &
277         od865aer, abs550aer, od550lt1aer, sconcso4, sconcno3, &
278         sconcoa, sconcbc, sconcss, sconcdust, concso4, concno3, &
279         concoa, concbc, concss, concdust, loadso4, &
280         loadoa, loadbc, loadss, loaddust, loadno3, tausum_aero, drytausum_aero, &
281         topswad_aero, topswad0_aero, solswad_aero, &
282         solswad0_aero, topsw_aero, solsw_aero, &
283         topsw0_aero, solsw0_aero, topswcf_aero, &
284         solswcf_aero, topswai_aero, solswai_aero, &
285         toplwad_aero, toplwad0_aero, sollwad_aero, &
286         sollwad0_aero, toplwai_aero, sollwai_aero, &
287         scdnc, cldncl, reffclws, reffclwc, cldnvi, stratomask,&
288         lcc, lcc3d, lcc3dcon, lcc3dstra, &
289         icc3dcon, icc3dstra, zfice, reffclwtop, &
290         ec550aer, flwc, fiwc, t_seri, theta, q_seri, &
291         ql_seri, qs_seri, tr_seri, &
292         zphi, u_seri, v_seri, omega, cldfra, &
293         rneb, rnebjn, rneblsvol, zx_rh, d_t_dyn,  &
294         d_q_dyn,  d_ql_dyn, d_qs_dyn, &
295         d_q_dyn2d,  d_ql_dyn2d, d_qs_dyn2d, &
296         d_u_dyn, d_v_dyn, d_t_con, d_t_ajsb, d_t_ajs, &
297         d_u_ajs, d_v_ajs, &
298         d_u_con, d_v_con, d_q_con, d_q_ajs, d_t_lsc, &
299         d_t_lwr,d_t_lw0,d_t_swr,d_t_sw0, &
300         d_t_eva, d_q_lsc, beta_prec, d_t_lscth, &
301         d_t_lscst, d_q_lscth, d_q_lscst, plul_th, &
302         plul_st, d_t_vdf, d_t_diss, d_q_vdf, d_q_eva, &
303         zw2, fraca, zmax_th, d_q_ajsb, d_t_ec, d_u_vdf, &
304         d_v_vdf, d_u_oro, d_v_oro, d_t_oro, d_u_lif, &
305         d_v_lif, d_t_lif, du_gwd_hines, dv_gwd_hines, d_t_hin, &
306         dv_gwd_rando, dv_gwd_front, &
307         east_gwstress, west_gwstress, &
308         d_q_ch4, pmfd, pmfu, ref_liq, ref_ice, rhwriteSTD, &
309         ep, epmax_diag, &  ! epmax_cape
310         p_tropopause, t_tropopause, z_tropopause
311
312#ifdef CPP_StratAer
313    USE phys_local_var_mod, ONLY:  &
314         budg_3D_nucl, budg_3D_cond_evap, budg_3D_ocs_to_so2, budg_3D_so2_to_h2so4, &
315         budg_sed_part, R2SO4, OCS_lifetime, SO2_lifetime, &
316         budg_3D_backgr_ocs, budg_3D_backgr_so2, &
317         budg_dep_dry_ocs, budg_dep_wet_ocs, &
318         budg_dep_dry_so2, budg_dep_wet_so2, &
319         budg_dep_dry_h2so4, budg_dep_wet_h2so4, &
320         budg_dep_dry_part, budg_dep_wet_part, &
321         budg_emi_ocs, budg_emi_so2, budg_emi_h2so4, budg_emi_part, &
322         budg_ocs_to_so2, budg_so2_to_h2so4, budg_h2so4_to_part, &
323         surf_PM25_sulf, tau_strat_550, tausum_strat, &
324         vsed_aer, tau_strat_1020, f_r_wet
325#endif
326
327#ifdef REPROBUS
328    USE CHEM_REP, ONLY : nas, nbnas, tnamenas, ttextnas
329#endif
330
331    USE phys_output_var_mod, ONLY: vars_defined, snow_o, zfra_o, bils_diss, &
332         bils_ec,bils_ech, bils_tke, bils_kinetic, bils_latent, bils_enthalp, &
333         itau_con, nfiles, clef_files, nid_files, dryaod_diag, &
334         zustr_gwd_hines, zvstr_gwd_hines,zustr_gwd_rando, zvstr_gwd_rando, &
335         zustr_gwd_front, zvstr_gwd_front, sza_o,    &
336         sens_prec_liq_o, sens_prec_sol_o, lat_prec_liq_o, lat_prec_sol_o, &
337         cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv, &
338! Marine
339         map_prop_hc, map_prop_hist, &
340         map_emis_hc,map_iwp_hc,map_deltaz_hc,&
341         map_pcld_hc,map_tcld_hc,&
342         map_emis_hist,map_iwp_hist,map_deltaz_hist,&
343         map_rad_hist,&
344         map_ntot,map_hc,map_hist,&
345         map_Cb,map_ThCi,map_Anv,&
346         map_emis_Cb,map_pcld_Cb,map_tcld_Cb,&
347         map_emis_ThCi,map_pcld_ThCi,map_tcld_ThCi,&
348         map_emis_Anv,map_pcld_Anv,map_tcld_Anv, &
349         alt_tropo, &
350!Ionela
351         ok_4xCO2atm
352
353    USE ocean_slab_mod, ONLY: nslay, tslab, slab_bilg, tice, seaice, &
354        slab_ekman,slab_hdiff,slab_gm,dt_ekman, dt_hdiff, dt_gm, dt_qflux
355    USE pbl_surface_mod, ONLY: snow
356    USE indice_sol_mod, ONLY: nbsrf
357    USE infotrac_phy, ONLY: nqtot, nqo, type_trac, tname, niadv
358    USE geometry_mod, ONLY: cell_area, latitude_deg, longitude_deg
359    USE surface_data, ONLY: type_ocean, version_ocean, ok_veget, ok_snow
360    USE aero_mod, ONLY: naero_tot, id_STRAT_phy
361    USE ioipsl, ONLY: histend, histsync
362    USE iophy, ONLY: set_itau_iophy, histwrite_phy
363    USE netcdf, ONLY: nf90_fill_real
364    USE print_control_mod, ONLY: prt_level,lunout
365
366
367#ifdef CPP_XIOS
368    ! ug Pour les sorties XIOS
369    USE xios
370    USE wxios, ONLY: wxios_closedef, missing_val
371#endif
372    USE phys_cal_mod, ONLY : mth_len
373
374#ifdef CPP_RRTM
375    USE YOESW, ONLY : RSUN
376#endif
377    USE tracinca_mod, ONLY: config_inca
378
379    IMPLICIT NONE
380
381    INCLUDE "clesphys.h"
382    INCLUDE "thermcell.h"
383    INCLUDE "compbl.h"
384    INCLUDE "YOMCST.h"
385
386    ! Input
387    INTEGER :: itap, ivap, iliq, isol, read_climoz
388    INTEGER, DIMENSION(klon) :: lmax_th
389    LOGICAL :: aerosol_couple, ok_sync
390    LOGICAL :: ok_ade, ok_aie, new_aod
391    LOGICAL, DIMENSION(klon, klev) :: ptconv, ptconvth
392    REAL :: pdtphys
393    CHARACTER (LEN=4), DIMENSION(nlevSTD) :: clevSTD
394    REAL, DIMENSION(klon,nlevSTD) :: zx_tmp_fi3d_STD
395    REAL, DIMENSION(klon) :: pphis
396    REAL, DIMENSION(klon, klev) :: pplay, d_u, d_t
397    REAL, DIMENSION(klon, klev+1) :: paprs
398    REAL, DIMENSION(klon,klev,nqtot) :: qx, d_qx
399    REAL, DIMENSION(klon, klev) :: zmasse
400    INTEGER :: flag_aerosol_strat
401    INTEGER :: flag_aerosol
402    LOGICAL :: ok_cdnc
403    REAL, DIMENSION(3) :: freq_moyNMC
404
405    ! Local
406    INTEGER :: itau_w
407    INTEGER :: i, iinit, iinitend=1, iff, iq, iiq, nsrf, k, ll, naero
408    REAL, DIMENSION (klon) :: zx_tmp_fi2d, zpt_conv2d
409    REAL, DIMENSION (klon,klev) :: zx_tmp_fi3d, zpt_conv
410    REAL, DIMENSION (klon,klev+1) :: zx_tmp_fi3d1
411    REAL, DIMENSION (klon,NSW) :: zx_tmp_fi3dsp
412    CHARACTER (LEN=4)              :: bb2
413    INTEGER, DIMENSION(nbp_lon*nbp_lat)  :: ndex2d
414    INTEGER, DIMENSION(nbp_lon*nbp_lat*klev) :: ndex3d
415    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
416!   REAL, PARAMETER :: missing_val=nf90_fill_real
417    REAL, DIMENSION(klev+1,2) :: Ahyb_bounds, Bhyb_bounds
418    REAL, DIMENSION(klev,2) :: Ahyb_mid_bounds, Bhyb_mid_bounds
419    INTEGER :: ilev
420#ifndef CPP_XIOS
421    REAL :: missing_val
422#endif
423    REAL, PARAMETER :: un_jour=86400.
424    INTEGER ISW
425    CHARACTER*1 ch1
426    CHARACTER*20 varname
427
428#ifdef CPP_XIOS
429    TYPE(xios_fieldgroup) :: group_handle
430    TYPE(xios_field) :: child
431#endif
432#ifdef CPP_StratAer
433    LOGICAL, PARAMETER :: debug_strataer=.FALSE.
434#endif
435
436    ! On calcul le nouveau tau:
437    itau_w = itau_phy + itap
438    ! On le donne à iophy pour que les histwrite y aient accès:
439    CALL set_itau_iophy(itau_w)
440
441    IF (.NOT.vars_defined) THEN
442       iinitend = 2
443    ELSE
444       iinitend = 1
445    ENDIF
446
447    Ahyb_bounds(1,1) = 0.
448    Ahyb_bounds(1,2) = aps(1)
449    Bhyb_bounds(1,1) = 1.
450    Bhyb_bounds(1,2) = bps(1)   
451    DO ilev=2,klev
452      Ahyb_bounds(ilev,1) = aps(ilev-1)
453      Ahyb_bounds(ilev,2) = aps(ilev)
454      Bhyb_bounds(ilev,1) = bps(ilev-1)
455      Bhyb_bounds(ilev,2) = bps(ilev)
456    ENDDO
457     Ahyb_bounds(klev+1,1) = aps(klev)
458     Ahyb_bounds(klev+1,2) = 0.
459     Bhyb_bounds(klev+1,1) = bps(klev)
460     Bhyb_bounds(klev+1,2) = 0.
461
462    DO ilev=1, klev
463      Ahyb_mid_bounds(ilev,1) = ap(ilev)
464      Ahyb_mid_bounds(ilev,2) = ap(ilev+1)
465      Bhyb_mid_bounds(ilev,1) = bp(ilev)
466      Bhyb_mid_bounds(ilev,2) = bp(ilev+1)
467    END DO
468
469#ifdef CPP_XIOS
470#ifdef CPP_StratAer
471!$OMP MASTER
472   IF (.NOT.vars_defined) THEN
473          !On ajoute les variables 3D traceurs par l interface fortran
474          CALL xios_get_handle("fields_strataer_trac_3D", group_handle)
475          ! On boucle sur les traceurs pour les ajouter au groupe puis fixer les attributs
476          DO iq=nqo+1, nqtot
477            iiq=niadv(iq)
478            varname=trim(tname(iiq))
479            WRITE (lunout,*) 'XIOS var=', nqo, iq, nqtot, varname
480            CALL xios_add_child(group_handle, child, varname)
481            CALL xios_set_attr(child, name=varname, unit="kg kg-1")
482            varname='d'//trim(tname(iiq))//'_vdf'
483            CALL xios_add_child(group_handle, child, varname)
484            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
485            varname='d'//trim(tname(iiq))//'_the'
486            CALL xios_add_child(group_handle, child, varname)
487            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
488            varname='d'//trim(tname(iiq))//'_con'
489            CALL xios_add_child(group_handle, child, varname)
490            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
491            varname='d'//trim(tname(iiq))//'_lessi_impa'
492            CALL xios_add_child(group_handle, child, varname)
493            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
494            varname='d'//trim(tname(iiq))//'_lessi_nucl'
495            CALL xios_add_child(group_handle, child, varname)
496            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
497            varname='d'//trim(tname(iiq))//'_insc'
498            CALL xios_add_child(group_handle, child, varname)
499            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
500            varname='d'//trim(tname(iiq))//'_bcscav'
501            CALL xios_add_child(group_handle, child, varname)
502            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
503            varname='d'//trim(tname(iiq))//'_evapls'
504            CALL xios_add_child(group_handle, child, varname)
505            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
506            varname='d'//trim(tname(iiq))//'_ls'
507            CALL xios_add_child(group_handle, child, varname)
508            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
509            varname='d'//trim(tname(iiq))//'_trsp'
510            CALL xios_add_child(group_handle, child, varname)
511            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
512            varname='d'//trim(tname(iiq))//'_sscav'
513            CALL xios_add_child(group_handle, child, varname)
514            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
515            varname='d'//trim(tname(iiq))//'_sat'
516            CALL xios_add_child(group_handle, child, varname)
517            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
518            varname='d'//trim(tname(iiq))//'_uscav'
519            CALL xios_add_child(group_handle, child, varname)
520            CALL xios_set_attr(child, name=varname, unit="kg kg-1 s-1")
521          ENDDO
522          !On ajoute les variables 2D traceurs par l interface fortran
523          CALL xios_get_handle("fields_strataer_trac_2D", group_handle)
524          ! On boucle sur les traceurs pour les ajouter au groupe puis fixer les attributs
525          DO iq=nqo+1, nqtot
526            iiq=niadv(iq)
527            varname='cum'//trim(tname(iiq))
528            WRITE (lunout,*) 'XIOS var=', iq, nqtot, varname
529            CALL xios_add_child(group_handle, child, varname)
530            CALL xios_set_attr(child, name=varname, unit="kg m-2")
531            varname='cumd'//trim(tname(iiq))//'_dry'
532            CALL xios_add_child(group_handle, child, varname)
533            CALL xios_set_attr(child, name=varname, unit="kg m-2 s-1")
534          ENDDO
535    ENDIF
536!$OMP END MASTER
537#endif
538#endif
539    ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
540    DO iinit=1, iinitend
541!      print *,'IFF iinit=', iinit, iinitend
542#ifdef CPP_XIOS
543       !$OMP MASTER
544       IF (vars_defined) THEN
545          IF (prt_level >= 10) then
546             write(lunout,*)"phys_output_write: call xios_update_calendar, itau_w=",itau_w
547          ENDIF
548!          CALL xios_update_calendar(itau_w)
549          CALL xios_update_calendar(itap)
550       ENDIF
551       !$OMP END MASTER
552       !$OMP BARRIER
553#endif
554       ! On procède à l'écriture ou à la définition des nombreuses variables:
555!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
556       CALL histwrite_phy(o_phis, pphis)
557
558       zx_tmp_fi2d = cell_area
559       IF (is_north_pole_phy) then
560         zx_tmp_fi2d(1) = cell_area(1)/nbp_lon
561       ENDIF
562       IF (is_south_pole_phy) then
563         zx_tmp_fi2d(klon) = cell_area(klon)/nbp_lon
564       ENDIf
565       CALL histwrite_phy(o_aire, zx_tmp_fi2d)
566
567       IF (vars_defined) THEN
568          DO i=1, klon
569             zx_tmp_fi2d(i)=pctsrf(i,is_ter)+pctsrf(i,is_lic)
570          ENDDO
571       ENDIF
572
573       CALL histwrite_phy(o_contfracATM, zx_tmp_fi2d)
574       CALL histwrite_phy(o_contfracOR, pctsrf(:,is_ter))
575!
576#ifdef CPP_XIOS
577       CALL histwrite_phy("R_ecc",R_ecc)
578       CALL histwrite_phy("R_peri",R_peri)
579       CALL histwrite_phy("R_incl",R_incl)
580       CALL histwrite_phy("solaire",solaire)
581       CALL histwrite_phy(o_Ahyb, ap)
582       CALL histwrite_phy(o_Bhyb, bp)
583       CALL histwrite_phy(o_Ahyb_bounds, Ahyb_bounds)
584       CALL histwrite_phy(o_Bhyb_bounds, Bhyb_bounds)
585       CALL histwrite_phy(o_Ahyb_mid, aps)
586       CALL histwrite_phy(o_Bhyb_mid, bps)
587       CALL histwrite_phy(o_Ahyb_mid_bounds, Ahyb_mid_bounds)
588       CALL histwrite_phy(o_Bhyb_mid_bounds, Bhyb_mid_bounds)
589       CALL histwrite_phy(o_longitude, longitude_deg)
590       CALL histwrite_phy(o_latitude, latitude_deg)
591!
592#ifdef CPP_RRTM
593      IF (iflag_rrtm.EQ.1) THEN
594        DO ISW=1, NSW
595          WRITE(ch1,'(i1)') ISW
596!         zx_tmp_0d=RSUN(ISW)
597!         CALL histwrite_phy("rsun"//ch1,zx_tmp_0d)
598          CALL histwrite_phy("rsun"//ch1,RSUN(ISW))
599        ENDDO
600      ENDIF
601#endif
602!
603       CALL histwrite_phy("co2_ppm",co2_ppm)
604       CALL histwrite_phy("CH4_ppb",CH4_ppb)
605       CALL histwrite_phy("N2O_ppb",N2O_ppb)
606       CALL histwrite_phy("CFC11_ppt",CFC11_ppt)
607       CALL histwrite_phy("CFC12_ppt",CFC12_ppt)
608!
609#endif
610
611!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
612! Simulateur AIRS
613     IF (ok_airs) then
614      CALL histwrite_phy(o_alt_tropo,alt_tropo)
615 
616      CALL histwrite_phy(o_map_prop_hc,map_prop_hc)
617      CALL histwrite_phy(o_map_prop_hist,map_prop_hist)
618
619      CALL histwrite_phy(o_map_emis_hc,map_emis_hc)
620      CALL histwrite_phy(o_map_iwp_hc,map_iwp_hc)
621      CALL histwrite_phy(o_map_deltaz_hc,map_deltaz_hc)
622      CALL histwrite_phy(o_map_pcld_hc,map_pcld_hc)
623      CALL histwrite_phy(o_map_tcld_hc,map_tcld_hc)
624
625      CALL histwrite_phy(o_map_emis_hist,map_emis_hist)
626      CALL histwrite_phy(o_map_iwp_hist,map_iwp_hist)
627      CALL histwrite_phy(o_map_deltaz_hist,map_deltaz_hist)
628
629      CALL histwrite_phy(o_map_ntot,map_ntot)
630      CALL histwrite_phy(o_map_hc,map_hc)
631      CALL histwrite_phy(o_map_hist,map_hist)
632
633      CALL histwrite_phy(o_map_Cb,map_Cb)
634      CALL histwrite_phy(o_map_ThCi,map_ThCi)
635      CALL histwrite_phy(o_map_Anv,map_Anv)
636
637      CALL histwrite_phy(o_map_emis_Cb,map_emis_Cb)
638      CALL histwrite_phy(o_map_pcld_Cb,map_pcld_Cb)
639      CALL histwrite_phy(o_map_tcld_Cb,map_tcld_Cb)
640
641      CALL histwrite_phy(o_map_emis_ThCi,map_emis_ThCi)
642      CALL histwrite_phy(o_map_pcld_ThCi,map_pcld_ThCi)
643      CALL histwrite_phy(o_map_tcld_ThCi,map_tcld_ThCi)
644
645      CALL histwrite_phy(o_map_emis_Anv,map_emis_Anv)
646      CALL histwrite_phy(o_map_pcld_Anv,map_pcld_Anv)
647      CALL histwrite_phy(o_map_tcld_Anv,map_tcld_Anv)
648     ENDIF
649
650       CALL histwrite_phy(o_sza, sza_o)
651       CALL histwrite_phy(o_flat, zxfluxlat)
652       CALL histwrite_phy(o_ptstar, ptstar)
653       CALL histwrite_phy(o_pt0, pt0)
654       CALL histwrite_phy(o_slp, slp)
655       CALL histwrite_phy(o_tsol, zxtsol)
656       CALL histwrite_phy(o_t2m, zt2m_cor)
657       CALL histwrite_phy(o_t2m_min, zt2m_cor)
658       CALL histwrite_phy(o_t2m_max, zt2m_cor)
659       CALL histwrite_phy(o_t2m_max_mon, t2m_max_mon)
660       CALL histwrite_phy(o_t2m_min_mon, t2m_min_mon)
661
662       IF (vars_defined) THEN
663          DO i=1, klon
664             zx_tmp_fi2d(i)=SQRT(zu10m_cor(i)*zu10m_cor(i)+zv10m_cor(i)*zv10m_cor(i))
665          ENDDO
666       ENDIF
667       CALL histwrite_phy(o_wind10m, zx_tmp_fi2d)
668
669       IF (vars_defined) THEN
670          DO i=1, klon
671             zx_tmp_fi2d(i)=SQRT(zu10m_cor(i)*zu10m_cor(i)+zv10m_cor(i)*zv10m_cor(i))
672          ENDDO
673       ENDIF
674       CALL histwrite_phy(o_wind10max, zx_tmp_fi2d)
675
676       CALL histwrite_phy(o_gusts, gustiness)
677
678       IF (vars_defined) THEN
679          DO i = 1, klon
680             zx_tmp_fi2d(i) = pctsrf(i,is_sic)
681          ENDDO
682       ENDIF
683       CALL histwrite_phy(o_sicf, zx_tmp_fi2d)
684       CALL histwrite_phy(o_q2m, zq2m_cor)
685       CALL histwrite_phy(o_ustar, zustar)
686       CALL histwrite_phy(o_u10m, zu10m_cor)
687       CALL histwrite_phy(o_v10m, zv10m_cor)
688
689       IF (vars_defined) THEN
690          DO i = 1, klon
691             zx_tmp_fi2d(i) = paprs(i,1)
692          ENDDO
693       ENDIF
694       CALL histwrite_phy(o_psol, zx_tmp_fi2d)
695       CALL histwrite_phy(o_mass, zmasse)
696       CALL histwrite_phy(o_qsurf, zxqsurf)
697
698       IF (.NOT. ok_veget) THEN
699          CALL histwrite_phy(o_qsol, qsol)
700       ENDIF
701
702       IF (vars_defined) THEN
703          DO i = 1, klon
704             zx_tmp_fi2d(i) = rain_fall(i) + snow_fall(i)
705          ENDDO
706       ENDIF
707
708       CALL histwrite_phy(o_precip, zx_tmp_fi2d)
709       CALL histwrite_phy(o_rain_fall, rain_fall)
710       CALL histwrite_phy(o_ndayrain, nday_rain)
711
712       ! epmax_cape:
713!       CALL histwrite_phy(o_epmax_diag, epmax_diag)
714       CALL histwrite_phy(o_ep, ep)
715
716       IF (vars_defined) THEN
717          DO i = 1, klon
718             zx_tmp_fi2d(i) = rain_lsc(i) + snow_lsc(i)
719          ENDDO
720       ENDIF
721       CALL histwrite_phy(o_plul, zx_tmp_fi2d)
722       CALL histwrite_phy(o_plun, rain_num)
723
724       IF (vars_defined) THEN
725          DO i = 1, klon
726             zx_tmp_fi2d(i) = rain_con(i) + snow_con(i)
727          ENDDO
728       ENDIF
729       CALL histwrite_phy(o_rain_con, rain_con)
730       CALL histwrite_phy(o_pluc, zx_tmp_fi2d)
731       CALL histwrite_phy(o_snow, snow_fall)
732       CALL histwrite_phy(o_msnow, zxsnow)
733       CALL histwrite_phy(o_fsnow, zfra_o)
734       CALL histwrite_phy(o_evap, evap)
735       CALL histwrite_phy(o_tops, topsw*swradcorr)
736       CALL histwrite_phy(o_tops0, topsw0*swradcorr)
737       CALL histwrite_phy(o_topl, toplw)
738       CALL histwrite_phy(o_topl0, toplw0)
739
740       IF (vars_defined) THEN
741          zx_tmp_fi2d(:) = swup(:,klevp1)*swradcorr(:)
742       ENDIF
743       CALL histwrite_phy(o_SWupTOA, zx_tmp_fi2d)
744
745       IF (vars_defined) THEN
746          zx_tmp_fi2d(:) = swup0(:,klevp1)*swradcorr(:)
747       ENDIF
748       CALL histwrite_phy(o_SWupTOAclr, zx_tmp_fi2d)
749
750       IF (vars_defined) THEN
751          zx_tmp_fi2d(:) = swupc0(:,klevp1)*swradcorr(:)
752       ENDIF
753       CALL histwrite_phy(o_SWupTOAcleanclr, zx_tmp_fi2d)
754
755       IF (vars_defined) THEN
756          zx_tmp_fi2d(:) = swdn(:,klevp1)*swradcorr(:)
757       ENDIF
758       CALL histwrite_phy(o_SWdnTOA, zx_tmp_fi2d)
759
760       IF (vars_defined) THEN
761          zx_tmp_fi2d(:) = swdn0(:,klevp1)*swradcorr(:)
762       ENDIF
763       CALL histwrite_phy(o_SWdnTOAclr, zx_tmp_fi2d)
764
765       IF (vars_defined) THEN
766          zx_tmp_fi2d(:) = topsw(:)*swradcorr(:)-toplw(:)
767       ENDIF
768       CALL histwrite_phy(o_nettop, zx_tmp_fi2d)
769       CALL histwrite_phy(o_SWup200, SWup200*swradcorr)
770       CALL histwrite_phy(o_SWup200clr, SWup200clr*swradcorr)
771       CALL histwrite_phy(o_SWdn200, SWdn200*swradcorr)
772       CALL histwrite_phy(o_SWdn200clr, SWdn200clr*swradcorr)
773       CALL histwrite_phy(o_LWup200, LWup200)
774       CALL histwrite_phy(o_LWup200clr, LWup200clr)
775       CALL histwrite_phy(o_LWdn200, LWdn200)
776       CALL histwrite_phy(o_LWdn200clr, LWdn200clr)
777       CALL histwrite_phy(o_sols, solsw*swradcorr)
778       CALL histwrite_phy(o_sols0, solsw0*swradcorr)
779       CALL histwrite_phy(o_soll, sollw)
780       CALL histwrite_phy(o_soll0, sollw0)
781       CALL histwrite_phy(o_radsol, radsol)
782
783       IF (vars_defined) THEN
784          zx_tmp_fi2d(:) = swup(:,1)*swradcorr(:)
785       ENDIF
786       CALL histwrite_phy(o_SWupSFC, zx_tmp_fi2d)
787
788       IF (vars_defined) THEN
789          zx_tmp_fi2d(:) = swup0(:,1)*swradcorr(:)
790       ENDIF
791       CALL histwrite_phy(o_SWupSFCclr, zx_tmp_fi2d)
792
793       IF (vars_defined) THEN
794          zx_tmp_fi2d(:) = swupc0(:,1)*swradcorr(:)
795       ENDIF
796       CALL histwrite_phy(o_SWupSFCcleanclr, zx_tmp_fi2d)
797
798       IF (vars_defined) THEN
799          zx_tmp_fi2d(:) = swdn(:,1)*swradcorr(:)
800       ENDIF
801       CALL histwrite_phy(o_SWdnSFC, zx_tmp_fi2d)
802
803       IF (vars_defined) THEN
804          zx_tmp_fi2d(:) = swdn0(:,1)*swradcorr(:)
805       ENDIF
806       CALL histwrite_phy(o_SWdnSFCclr, zx_tmp_fi2d)
807
808       IF (vars_defined) THEN
809          zx_tmp_fi2d(:) = swdnc0(:,1)*swradcorr(:)
810       ENDIF
811       CALL histwrite_phy(o_SWdnSFCcleanclr, zx_tmp_fi2d)
812
813       IF (vars_defined) THEN
814          zx_tmp_fi2d(:)=sollwdown(:)-sollw(:)
815       ENDIF
816       CALL histwrite_phy(o_LWupSFC, zx_tmp_fi2d)
817       CALL histwrite_phy(o_LWdnSFC, sollwdown)
818
819       IF (vars_defined) THEN
820          sollwdownclr(1:klon) = -1.*lwdn0(1:klon,1)
821          zx_tmp_fi2d(1:klon)=sollwdownclr(1:klon)-sollw0(1:klon)
822       ENDIF
823       CALL histwrite_phy(o_LWupSFCclr, zx_tmp_fi2d)
824       CALL histwrite_phy(o_LWdnSFCclr, sollwdownclr)
825
826       IF (vars_defined) THEN
827          zx_tmp_fi2d(:) = lwupc0(:,klevp1)
828       ENDIF
829       CALL histwrite_phy(o_LWupTOAcleanclr, zx_tmp_fi2d)
830       IF (vars_defined) THEN
831          zx_tmp_fi2d(:) = -1.*lwdnc0(:,1)
832       ENDIF
833       CALL histwrite_phy(o_LWdnSFCcleanclr, zx_tmp_fi2d)
834
835       CALL histwrite_phy(o_bils, bils)
836       CALL histwrite_phy(o_bils_diss, bils_diss)
837       CALL histwrite_phy(o_bils_ec, bils_ec)
838       CALL histwrite_phy(o_bils_ech, bils_ech)
839       CALL histwrite_phy(o_bils_tke, bils_tke)
840       CALL histwrite_phy(o_bils_kinetic, bils_kinetic)
841       CALL histwrite_phy(o_bils_latent, bils_latent)
842       CALL histwrite_phy(o_bils_enthalp, bils_enthalp)
843
844       IF (vars_defined) THEN
845          zx_tmp_fi2d(1:klon)=-1*sens(1:klon)
846       ENDIF
847       CALL histwrite_phy(o_sens, zx_tmp_fi2d)
848       CALL histwrite_phy(o_fder, fder)
849       CALL histwrite_phy(o_ffonte, zxffonte)
850       CALL histwrite_phy(o_fqcalving, zxfqcalving)
851       CALL histwrite_phy(o_fqfonte, zxfqfonte)
852       IF (vars_defined) THEN
853          zx_tmp_fi2d(1:klon)=(zxfqfonte(1:klon)+rain_fall(1:klon))*pctsrf(1:klon,is_lic)
854       ENDIF
855       CALL histwrite_phy(o_mrroli, zx_tmp_fi2d)
856       CALL histwrite_phy(o_runofflic, zxrunofflic)
857       IF (vars_defined) THEN
858          zx_tmp_fi2d=0.
859          DO nsrf=1,nbsrf
860             zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxu(:,1,nsrf)
861          ENDDO
862       ENDIF
863       CALL histwrite_phy(o_taux, zx_tmp_fi2d)
864
865       IF (vars_defined) THEN
866          zx_tmp_fi2d=0.
867          DO nsrf=1,nbsrf
868             zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+pctsrf(:,nsrf)*fluxv(:,1,nsrf)
869          ENDDO
870       ENDIF
871       CALL histwrite_phy(o_tauy, zx_tmp_fi2d)
872
873       IF (ok_snow) THEN
874          CALL histwrite_phy(o_snowsrf, snow_o)
875          CALL histwrite_phy(o_qsnow, qsnow)
876          CALL histwrite_phy(o_snowhgt,snowhgt)
877          CALL histwrite_phy(o_toice,to_ice)
878          CALL histwrite_phy(o_sissnow,sissnow)
879          CALL histwrite_phy(o_runoff,runoff)
880          CALL histwrite_phy(o_albslw3,albsol3_lic)
881       ENDIF
882
883       DO nsrf = 1, nbsrf
884
885          IF (vars_defined)             zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)*100.
886          CALL histwrite_phy(o_pourc_srf(nsrf), zx_tmp_fi2d)
887          IF (vars_defined)           zx_tmp_fi2d(1 : klon) = pctsrf( 1 : klon, nsrf)
888          CALL histwrite_phy(o_fract_srf(nsrf), zx_tmp_fi2d)
889          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fluxu( 1 : klon, 1, nsrf)
890          CALL histwrite_phy(o_taux_srf(nsrf), zx_tmp_fi2d)
891          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fluxv( 1 : klon, 1, nsrf)
892          CALL histwrite_phy(o_tauy_srf(nsrf), zx_tmp_fi2d)
893          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = ftsol( 1 : klon, nsrf)
894          CALL histwrite_phy(o_tsol_srf(nsrf), zx_tmp_fi2d)
895          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = evap_pot( 1 : klon, nsrf)
896          CALL histwrite_phy(o_evappot_srf(nsrf), zx_tmp_fi2d)
897          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = ustar(1 : klon, nsrf)
898          CALL histwrite_phy(o_ustar_srf(nsrf), zx_tmp_fi2d)
899          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = u10m(1 : klon, nsrf)
900          CALL histwrite_phy(o_u10m_srf(nsrf), zx_tmp_fi2d)
901          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = v10m(1 : klon, nsrf)
902          CALL histwrite_phy(o_v10m_srf(nsrf), zx_tmp_fi2d)
903          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = t2m(1 : klon, nsrf)
904          CALL histwrite_phy(o_t2m_srf(nsrf), zx_tmp_fi2d)
905          IF (vars_defined)       zx_tmp_fi2d(1 : klon) = fevap(1 : klon, nsrf)
906          CALL histwrite_phy(o_evap_srf(nsrf), zx_tmp_fi2d)
907          IF (vars_defined)        zx_tmp_fi2d(1 : klon) = fluxt( 1 : klon, 1, nsrf)
908          CALL histwrite_phy(o_sens_srf(nsrf), zx_tmp_fi2d)
909          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fluxlat( 1 : klon, nsrf)
910          CALL histwrite_phy(o_lat_srf(nsrf), zx_tmp_fi2d)
911          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fsollw( 1 : klon, nsrf)
912          CALL histwrite_phy(o_flw_srf(nsrf), zx_tmp_fi2d)
913          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, nsrf)
914          CALL histwrite_phy(o_fsw_srf(nsrf), zx_tmp_fi2d)
915          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = wfbils( 1 : klon, nsrf)
916          CALL histwrite_phy(o_wbils_srf(nsrf), zx_tmp_fi2d)
917          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = wfbilo( 1 : klon, nsrf)
918          CALL histwrite_phy(o_wbilo_srf(nsrf), zx_tmp_fi2d)
919          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = wfevap( 1 : klon, nsrf)
920          CALL histwrite_phy(o_wevap_srf(nsrf), zx_tmp_fi2d)
921          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = wfrain( 1 : klon, nsrf)
922          CALL histwrite_phy(o_wrain_srf(nsrf), zx_tmp_fi2d)
923          IF (vars_defined)         zx_tmp_fi2d(1 : klon) = wfsnow( 1 : klon, nsrf)
924          CALL histwrite_phy(o_wsnow_srf(nsrf), zx_tmp_fi2d)
925
926          IF (iflag_pbl > 1) THEN
927             CALL histwrite_phy(o_tke_srf(nsrf),  pbl_tke(:,1:klev,nsrf))
928             CALL histwrite_phy(o_l_mix(nsrf),  l_mix(:,1:klev,nsrf))
929             CALL histwrite_phy(o_l_mixmin(nsrf),  l_mixmin(:,1:klev,nsrf))
930             CALL histwrite_phy(o_tke_max_srf(nsrf),  pbl_tke(:,1:klev,nsrf))
931          ENDIF
932!jyg<
933          IF (iflag_pbl > 1 .AND. iflag_wake>=1  .AND. iflag_pbl_split >=1) THEN
934             CALL histwrite_phy(o_dltpbltke_srf(nsrf), wake_delta_pbl_TKE(:,1:klev,nsrf))
935          ENDIF
936!>jyg
937!          IF (iflag_pbl > 1 .AND. ifl_pbltree  >=1 ) THEN
938!       CALL histwrite_phy(o_treedrg_srf(nsrf), treedrg(:,1:klev,nsrf))
939!            ENDIF
940
941
942       ENDDO
943
944       IF (vars_defined) zx_tmp_fi2d(1 : klon) = sens_prec_liq_o(1 : klon, 1)
945       CALL histwrite_phy(o_sens_prec_liq_oce, zx_tmp_fi2d)       
946       IF (vars_defined) zx_tmp_fi2d(1 : klon) = sens_prec_liq_o(1 : klon, 2)
947       CALL histwrite_phy(o_sens_prec_liq_sic, zx_tmp_fi2d)       
948       IF (vars_defined) zx_tmp_fi2d(1 : klon) = sens_prec_sol_o(1 : klon, 1)
949       CALL histwrite_phy(o_sens_prec_sol_oce, zx_tmp_fi2d)       
950       IF (vars_defined) zx_tmp_fi2d(1 : klon) = sens_prec_sol_o(1 : klon, 2)
951       CALL histwrite_phy(o_sens_prec_sol_sic, zx_tmp_fi2d)       
952
953       IF (vars_defined) zx_tmp_fi2d(1 : klon) = lat_prec_liq_o(1 : klon, 1)
954       CALL histwrite_phy(o_lat_prec_liq_oce, zx_tmp_fi2d)       
955       IF (vars_defined) zx_tmp_fi2d(1 : klon) = lat_prec_liq_o(1 : klon, 2)
956       CALL histwrite_phy(o_lat_prec_liq_sic, zx_tmp_fi2d)       
957       IF (vars_defined) zx_tmp_fi2d(1 : klon) = lat_prec_sol_o(1 : klon, 1)
958       CALL histwrite_phy(o_lat_prec_sol_oce, zx_tmp_fi2d)       
959       IF (vars_defined) zx_tmp_fi2d(1 : klon) = lat_prec_sol_o(1 : klon, 2)
960       CALL histwrite_phy(o_lat_prec_sol_sic, zx_tmp_fi2d)       
961
962       DO nsrf=1,nbsrf+1
963          CALL histwrite_phy(o_wstar(nsrf), wstar(1 : klon, nsrf))
964       ENDDO
965
966       CALL histwrite_phy(o_cdrm, cdragm)
967       CALL histwrite_phy(o_cdrh, cdragh)
968       CALL histwrite_phy(o_cldl, cldl)
969       CALL histwrite_phy(o_cldm, cldm)
970       CALL histwrite_phy(o_cldh, cldh)
971       CALL histwrite_phy(o_cldt, cldt)
972       CALL histwrite_phy(o_JrNt, JrNt)
973       CALL histwrite_phy(o_cldljn, cldl*JrNt)
974       CALL histwrite_phy(o_cldmjn, cldm*JrNt)
975       CALL histwrite_phy(o_cldhjn, cldh*JrNt)
976       CALL histwrite_phy(o_cldtjn, cldt*JrNt)
977       CALL histwrite_phy(o_cldq, cldq)
978       IF (vars_defined)       zx_tmp_fi2d(1:klon) = flwp(1:klon)
979       CALL histwrite_phy(o_lwp, zx_tmp_fi2d)
980       IF (vars_defined)       zx_tmp_fi2d(1:klon) = fiwp(1:klon)
981       CALL histwrite_phy(o_iwp, zx_tmp_fi2d)
982       CALL histwrite_phy(o_ue, ue)
983       CALL histwrite_phy(o_ve, ve)
984       CALL histwrite_phy(o_uq, uq)
985       CALL histwrite_phy(o_vq, vq)
986       CALL histwrite_phy(o_uwat, uwat)
987       CALL histwrite_phy(o_vwat, vwat)
988       IF (iflag_con.GE.3) THEN ! sb
989          CALL histwrite_phy(o_cape, cape)
990          CALL histwrite_phy(o_pbase, ema_pcb)
991          CALL histwrite_phy(o_ptop, ema_pct)
992          CALL histwrite_phy(o_fbase, ema_cbmf)
993          IF (iflag_con /= 30) THEN
994             CALL histwrite_phy(o_plcl, plcl)
995             CALL histwrite_phy(o_plfc, plfc)
996             CALL histwrite_phy(o_wbeff, wbeff)
997             CALL histwrite_phy(o_convoccur, convoccur)
998          ENDIF
999
1000          CALL histwrite_phy(o_cape_max, cape)
1001
1002          CALL histwrite_phy(o_upwd, upwd)
1003          CALL histwrite_phy(o_Ma, Ma)
1004          CALL histwrite_phy(o_dnwd, dnwd)
1005          CALL histwrite_phy(o_dnwd0, dnwd0)
1006          !! The part relative to the frequency of occurence of convection
1007          !! is now grouped with the part relative to thermals and shallow
1008          !! convection (output of the 3 fields: ftime_deepcv, ftime_th and
1009          !!  ftime_con).
1010          IF (vars_defined) THEN
1011             IF (iflag_thermals>=1)THEN
1012                zx_tmp_fi3d=-dnwd+dnwd0+upwd+fm_therm(:,1:klev)
1013             ELSE
1014                zx_tmp_fi3d=-dnwd+dnwd0+upwd
1015             ENDIF
1016          ENDIF
1017          CALL histwrite_phy(o_mc, zx_tmp_fi3d)
1018       ENDIF !iflag_con .GE. 3
1019       CALL histwrite_phy(o_prw, prw)
1020       CALL histwrite_phy(o_prlw, prlw)
1021       CALL histwrite_phy(o_prsw, prsw)
1022       CALL histwrite_phy(o_s_pblh, s_pblh)
1023       CALL histwrite_phy(o_s_pblt, s_pblt)
1024       CALL histwrite_phy(o_s_lcl, s_lcl)
1025       CALL histwrite_phy(o_s_therm, s_therm)
1026       !IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
1027       !       IF (o_s_capCL%flag(iff)<=lev_files(iff)) THEN
1028       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1029       !    $o_s_capCL%name,itau_w,s_capCL)
1030       !       ENDIF
1031       !       IF (o_s_oliqCL%flag(iff)<=lev_files(iff)) THEN
1032       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1033       !    $o_s_oliqCL%name,itau_w,s_oliqCL)
1034       !       ENDIF
1035       !       IF (o_s_cteiCL%flag(iff)<=lev_files(iff)) THEN
1036       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1037       !    $o_s_cteiCL%name,itau_w,s_cteiCL)
1038       !       ENDIF
1039       !       IF (o_s_trmb1%flag(iff)<=lev_files(iff)) THEN
1040       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1041       !    $o_s_trmb1%name,itau_w,s_trmb1)
1042       !       ENDIF
1043       !       IF (o_s_trmb2%flag(iff)<=lev_files(iff)) THEN
1044       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1045       !    $o_s_trmb2%name,itau_w,s_trmb2)
1046       !       ENDIF
1047       !       IF (o_s_trmb3%flag(iff)<=lev_files(iff)) THEN
1048       !     CALL histwrite_phy(nid_files(iff),clef_stations(iff),
1049       !    $o_s_trmb3%name,itau_w,s_trmb3)
1050       !       ENDIF
1051
1052#ifdef CPP_IOIPSL
1053#ifndef CPP_XIOS
1054  IF (.NOT.ok_all_xml) THEN
1055       ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
1056       ! Champs interpolles sur des niveaux de pression
1057       missing_val=missing_val_nf90
1058       DO iff=1, nfiles
1059          ll=0
1060          DO k=1, nlevSTD
1061             bb2=clevSTD(k)
1062             IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
1063                  bb2.EQ."500".OR.bb2.EQ."200".OR. &
1064                  bb2.EQ."100".OR. &
1065                  bb2.EQ."50".OR.bb2.EQ."10") THEN
1066
1067                ! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1068                ll=ll+1
1069                CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
1070                CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
1071                CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
1072                CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
1073                CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
1074                CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
1075
1076             ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
1077          ENDDO
1078       ENDDO
1079  ENDIF
1080#endif
1081#endif
1082#ifdef CPP_XIOS
1083  IF (ok_all_xml) THEN
1084!XIOS  CALL xios_get_field_attr("u850",default_value=missing_val)
1085!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1086          ll=0
1087          DO k=1, nlevSTD
1088             bb2=clevSTD(k)
1089             IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
1090                bb2.EQ."500".OR.bb2.EQ."200".OR. &
1091                bb2.EQ."100".OR. &
1092                bb2.EQ."50".OR.bb2.EQ."10") THEN
1093                ll=ll+1
1094                CALL histwrite_phy(o_uSTDlevs(ll),ulevSTD(:,k))
1095                CALL histwrite_phy(o_vSTDlevs(ll),vlevSTD(:,k))
1096                CALL histwrite_phy(o_wSTDlevs(ll),wlevSTD(:,k))
1097                CALL histwrite_phy(o_zSTDlevs(ll),philevSTD(:,k))
1098                CALL histwrite_phy(o_qSTDlevs(ll),qlevSTD(:,k))
1099                CALL histwrite_phy(o_tSTDlevs(ll),tlevSTD(:,k))
1100             ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
1101          ENDDO
1102  ENDIF
1103#endif
1104       IF (vars_defined) THEN
1105          DO i=1, klon
1106             IF (pctsrf(i,is_oce).GT.epsfra.OR. &
1107                  pctsrf(i,is_sic).GT.epsfra) THEN
1108                zx_tmp_fi2d(i) = (ftsol(i, is_oce) * pctsrf(i,is_oce)+ &
1109                     ftsol(i, is_sic) * pctsrf(i,is_sic))/ &
1110                     (pctsrf(i,is_oce)+pctsrf(i,is_sic))
1111             ELSE
1112                zx_tmp_fi2d(i) = 273.15
1113             ENDIF
1114          ENDDO
1115       ENDIF
1116       CALL histwrite_phy(o_t_oce_sic, zx_tmp_fi2d)
1117
1118       ! Couplage convection-couche limite
1119       IF (iflag_con.GE.3) THEN
1120          IF (iflag_coupl>=1) THEN
1121             CALL histwrite_phy(o_ale_bl, ale_bl)
1122             CALL histwrite_phy(o_alp_bl, alp_bl)
1123          ENDIF !iflag_coupl>=1
1124       ENDIF !(iflag_con.GE.3)
1125       ! Wakes
1126       IF (iflag_con.EQ.3) THEN
1127          IF (iflag_wake>=1) THEN
1128             CALL histwrite_phy(o_ale_wk, ale_wake)
1129             CALL histwrite_phy(o_alp_wk, alp_wake)
1130             IF (iflag_pbl_split>=1) THEN
1131               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=dtvdf_x(1:klon,1:klev)/pdtphys
1132               CALL histwrite_phy(o_dtvdf_x    ,zx_tmp_fi3d)
1133               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=dtvdf_w(1:klon,1:klev)/pdtphys
1134               CALL histwrite_phy(o_dtvdf_w    ,zx_tmp_fi3d)
1135               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=dqvdf_x(1:klon,1:klev)/pdtphys
1136               CALL histwrite_phy(o_dqvdf_x    ,zx_tmp_fi3d)
1137               IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=dqvdf_w(1:klon,1:klev)/pdtphys
1138               CALL histwrite_phy(o_dqvdf_w    ,zx_tmp_fi3d)
1139               CALL histwrite_phy(o_sens_x     ,sens_x     )
1140               CALL histwrite_phy(o_sens_w     ,sens_w     )
1141               CALL histwrite_phy(o_flat_x     ,zxfluxlat_x)
1142               CALL histwrite_phy(o_flat_w     ,zxfluxlat_w)
1143               CALL histwrite_phy(o_delta_tsurf,delta_tsurf)
1144               CALL histwrite_phy(o_cdragh_x   ,cdragh_x   )
1145               CALL histwrite_phy(o_cdragh_w   ,cdragh_w   )
1146               CALL histwrite_phy(o_cdragm_x   ,cdragm_x   )
1147               CALL histwrite_phy(o_cdragm_w   ,cdragm_w   )
1148               CALL histwrite_phy(o_kh         ,kh         )
1149               CALL histwrite_phy(o_kh_x       ,kh_x       )
1150               CALL histwrite_phy(o_kh_w       ,kh_w       )
1151             ENDIF   ! (iflag_pbl_split>=1)
1152             CALL histwrite_phy(o_ale, ale)
1153             CALL histwrite_phy(o_alp, alp)
1154             CALL histwrite_phy(o_cin, cin)
1155             CALL histwrite_phy(o_WAPE, wake_pe)
1156             CALL histwrite_phy(o_wake_h, wake_h)
1157             CALL histwrite_phy(o_wake_s, wake_s)
1158             CALL histwrite_phy(o_wake_deltat, wake_deltat)
1159             CALL histwrite_phy(o_wake_deltaq, wake_deltaq)
1160             CALL histwrite_phy(o_wake_omg, wake_omg)
1161             IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_wake(1:klon,1:klev) &
1162                  /pdtphys
1163             CALL histwrite_phy(o_dtwak, zx_tmp_fi3d)
1164             IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_wake(1:klon,1:klev)/pdtphys
1165             CALL histwrite_phy(o_dqwak, zx_tmp_fi3d)
1166             CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1167             CALL histwrite_phy(o_dqwak2d, zx_tmp_fi2d)
1168          ENDIF ! iflag_wake>=1
1169          CALL histwrite_phy(o_ftd, ftd)
1170          CALL histwrite_phy(o_fqd, fqd)
1171       ENDIF !(iflag_con.EQ.3)
1172       IF (iflag_con.EQ.3.OR.iflag_con.EQ.30) THEN
1173          ! sortie RomP convection descente insaturee iflag_con=30
1174          ! etendue a iflag_con=3 (jyg)
1175          CALL histwrite_phy(o_Vprecip, Vprecip)
1176          CALL histwrite_phy(o_wdtrainA, wdtrainA)
1177          CALL histwrite_phy(o_wdtrainM, wdtrainM)
1178       ENDIF !(iflag_con.EQ.3.or.iflag_con.EQ.30)
1179!!! nrlmd le 10/04/2012
1180       IF (iflag_trig_bl>=1) THEN
1181          CALL histwrite_phy(o_n2, n2)
1182          CALL histwrite_phy(o_s2, s2)
1183          CALL histwrite_phy(o_proba_notrig, proba_notrig)
1184          CALL histwrite_phy(o_random_notrig, random_notrig)
1185          CALL histwrite_phy(o_ale_bl_stat, ale_bl_stat)
1186          CALL histwrite_phy(o_ale_bl_trig, ale_bl_trig)
1187       ENDIF  !(iflag_trig_bl>=1)
1188       IF (iflag_clos_bl>=1) THEN
1189          CALL histwrite_phy(o_alp_bl_det, alp_bl_det)
1190          CALL histwrite_phy(o_alp_bl_fluct_m, alp_bl_fluct_m)
1191          CALL histwrite_phy(o_alp_bl_fluct_tke,  &
1192               alp_bl_fluct_tke)
1193          CALL histwrite_phy(o_alp_bl_conv, alp_bl_conv)
1194          CALL histwrite_phy(o_alp_bl_stat, alp_bl_stat)
1195       ENDIF  !(iflag_clos_bl>=1)
1196!!! fin nrlmd le 10/04/2012
1197       ! Output of slab ocean variables
1198       IF (type_ocean=='slab ') THEN
1199          CALL histwrite_phy(o_slab_bils, slab_wfbils)
1200          IF (nslay.EQ.1) THEN
1201              zx_tmp_fi2d(:)=tslab(:,1)
1202              CALL histwrite_phy(o_tslab, zx_tmp_fi2d)
1203              zx_tmp_fi2d(:)=dt_qflux(:,1)
1204              CALL histwrite_phy(o_slab_qflux, zx_tmp_fi2d)
1205          ELSE
1206              CALL histwrite_phy(o_tslab, tslab(:,1:nslay))
1207              CALL histwrite_phy(o_slab_qflux, dt_qflux(:,1:nslay))
1208          ENDIF
1209          IF (version_ocean=='sicINT') THEN
1210              CALL histwrite_phy(o_slab_bilg, slab_bilg)
1211              CALL histwrite_phy(o_slab_tice, tice)
1212              CALL histwrite_phy(o_slab_sic, seaice)
1213          ENDIF
1214          IF (slab_gm) THEN
1215             CALL histwrite_phy(o_slab_gm, dt_gm(:,1:nslay))
1216          END IF
1217          IF (slab_hdiff) THEN
1218            IF (nslay.EQ.1) THEN
1219                zx_tmp_fi2d(:)=dt_hdiff(:,1)
1220                CALL histwrite_phy(o_slab_hdiff, zx_tmp_fi2d)
1221            ELSE
1222                CALL histwrite_phy(o_slab_hdiff, dt_hdiff(:,1:nslay))
1223            ENDIF
1224          ENDIF
1225          IF (slab_ekman.GT.0) THEN
1226            IF (nslay.EQ.1) THEN
1227                zx_tmp_fi2d(:)=dt_ekman(:,1)
1228                CALL histwrite_phy(o_slab_ekman, zx_tmp_fi2d)
1229            ELSE
1230                CALL histwrite_phy(o_slab_ekman, dt_ekman(:,1:nslay))
1231            ENDIF
1232          ENDIF
1233       ENDIF !type_ocean == force/slab
1234       CALL histwrite_phy(o_weakinv, weak_inversion)
1235       CALL histwrite_phy(o_dthmin, dthmin)
1236       CALL histwrite_phy(o_cldtau, cldtau)
1237       CALL histwrite_phy(o_cldemi, cldemi)
1238       CALL histwrite_phy(o_pr_con_l, pmflxr(:,1:klev))
1239       CALL histwrite_phy(o_pr_con_i, pmflxs(:,1:klev))
1240       CALL histwrite_phy(o_pr_lsc_l, prfl(:,1:klev))
1241       CALL histwrite_phy(o_pr_lsc_i, psfl(:,1:klev))
1242       CALL histwrite_phy(o_re, re)
1243       CALL histwrite_phy(o_fl, fl)
1244       IF (vars_defined) THEN
1245          DO i=1, klon
1246             zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
1247          ENDDO
1248       ENDIF
1249       CALL histwrite_phy(o_rh2m, zx_tmp_fi2d)
1250
1251!       IF (vars_defined) THEN
1252!          DO i=1, klon
1253!             zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
1254!          ENDDO
1255!       ENDIF
1256!       CALL histwrite_phy(o_rh2m_min, zx_tmp_fi2d)
1257
1258!       IF (vars_defined) THEN
1259!          DO i=1, klon
1260!             zx_tmp_fi2d(i)=MIN(100.,rh2m(i)*100.)
1261!          ENDDO
1262!       ENDIF
1263!       CALL histwrite_phy(o_rh2m_max, zx_tmp_fi2d)
1264
1265       CALL histwrite_phy(o_qsat2m, qsat2m)
1266       CALL histwrite_phy(o_tpot, tpot)
1267       CALL histwrite_phy(o_tpote, tpote)
1268       IF (vars_defined) zx_tmp_fi2d(1 : klon) = fsolsw( 1 : klon, is_ter)
1269       CALL histwrite_phy(o_SWnetOR,  zx_tmp_fi2d)
1270       IF (vars_defined) zx_tmp_fi2d(1:klon) = solsw(1:klon)/(1.-albsol1(1:klon))
1271       CALL histwrite_phy(o_SWdownOR,  zx_tmp_fi2d)
1272       CALL histwrite_phy(o_LWdownOR, sollwdown)
1273       CALL histwrite_phy(o_snowl, snow_lsc)
1274       CALL histwrite_phy(o_solldown, sollwdown)
1275       CALL histwrite_phy(o_dtsvdfo, d_ts(:,is_oce))
1276       CALL histwrite_phy(o_dtsvdft, d_ts(:,is_ter))
1277       CALL histwrite_phy(o_dtsvdfg,  d_ts(:,is_lic))
1278       CALL histwrite_phy(o_dtsvdfi, d_ts(:,is_sic))
1279       CALL histwrite_phy(o_z0m, z0m(:,nbsrf+1))
1280       CALL histwrite_phy(o_z0h, z0h(:,nbsrf+1))
1281
1282       ! od550 per species
1283!--OLIVIER
1284!This is warranted by treating INCA aerosols as offline aerosols
1285!       IF (new_aod .and. (.not. aerosol_couple)) THEN
1286       IF (new_aod) THEN
1287          IF (flag_aerosol.GT.0) THEN
1288             CALL histwrite_phy(o_od443aer, od443aer)
1289             CALL histwrite_phy(o_od550aer, od550aer)
1290             CALL histwrite_phy(o_od865aer, od865aer)
1291             CALL histwrite_phy(o_abs550aer, abs550aer)
1292             CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
1293             CALL histwrite_phy(o_sconcso4, sconcso4)
1294             CALL histwrite_phy(o_sconcno3, sconcno3)
1295             CALL histwrite_phy(o_sconcoa, sconcoa)
1296             CALL histwrite_phy(o_sconcbc, sconcbc)
1297             CALL histwrite_phy(o_sconcss, sconcss)
1298             CALL histwrite_phy(o_sconcdust, sconcdust)
1299             CALL histwrite_phy(o_concso4, concso4)
1300             CALL histwrite_phy(o_concno3, concno3)
1301             CALL histwrite_phy(o_concoa, concoa)
1302             CALL histwrite_phy(o_concbc, concbc)
1303             CALL histwrite_phy(o_concss, concss)
1304             CALL histwrite_phy(o_concdust, concdust)
1305             CALL histwrite_phy(o_loadso4, loadso4)
1306             CALL histwrite_phy(o_loadoa, loadoa)
1307             CALL histwrite_phy(o_loadbc, loadbc)
1308             CALL histwrite_phy(o_loadss, loadss)
1309             CALL histwrite_phy(o_loaddust, loaddust)
1310             CALL histwrite_phy(o_loadno3, loadno3)
1311             CALL histwrite_phy(o_dryod550aer, dryod550aer)
1312             DO naero = 1, naero_tot-1
1313                CALL histwrite_phy(o_drytausumaero(naero),drytausum_aero(:,naero))
1314             END DO
1315          ENDIF
1316          !--STRAT AER
1317          IF (flag_aerosol.GT.0.OR.flag_aerosol_strat.GT.0) THEN
1318             DO naero = 1, naero_tot
1319                CALL histwrite_phy(o_tausumaero(naero),tausum_aero(:,2,naero))
1320             END DO
1321          ENDIF
1322          IF (flag_aerosol_strat.GT.0) THEN
1323             CALL histwrite_phy(o_tausumaero_lw,tausum_aero(:,6,id_STRAT_phy))
1324          ENDIF
1325       ENDIF
1326
1327       CALL histwrite_phy(o_p_tropopause, p_tropopause)
1328       CALL histwrite_phy(o_t_tropopause, t_tropopause)
1329       CALL histwrite_phy(o_z_tropopause, z_tropopause)
1330
1331! ThL -- In the following, we assume read_climoz == 1
1332       zx_tmp_fi2d = 0.0    ! Computation for strato, added ThL
1333       DO k=1, klev
1334          zx_tmp_fi2d(:) = zx_tmp_fi2d(:) + wo(:,k,1) * stratomask(:,k) * 1.e3
1335       END DO
1336       CALL histwrite_phy(o_col_O3_strato, zx_tmp_fi2d) ! Added ThL
1337       zx_tmp_fi2d = 0.0    ! Computation for tropo, added ThL
1338       DO k=1, klev
1339          zx_tmp_fi2d(:) = zx_tmp_fi2d(:) + wo(:,k,1) * (1.0-stratomask(:,k)) * 1.e3
1340       END DO
1341       CALL histwrite_phy(o_col_O3_tropo, zx_tmp_fi2d)   ! Added ThL
1342! end add ThL
1343
1344#ifdef CPP_StratAer
1345       IF (type_trac=='coag') THEN
1346          CALL histwrite_phy(o_R2SO4, R2SO4)
1347          CALL histwrite_phy(o_OCS_lifetime, OCS_lifetime)
1348          CALL histwrite_phy(o_SO2_lifetime, SO2_lifetime)
1349          CALL histwrite_phy(o_budg_3D_backgr_ocs,   budg_3D_backgr_ocs)
1350          CALL histwrite_phy(o_budg_3D_backgr_so2,   budg_3D_backgr_so2)
1351          CALL histwrite_phy(o_budg_3D_ocs_to_so2,   budg_3D_ocs_to_so2)
1352          CALL histwrite_phy(o_budg_3D_so2_to_h2so4, budg_3D_so2_to_h2so4)
1353          CALL histwrite_phy(o_budg_3D_nucl,         budg_3D_nucl)
1354          CALL histwrite_phy(o_budg_3D_cond_evap,    budg_3D_cond_evap)
1355          CALL histwrite_phy(o_budg_dep_dry_ocs,     budg_dep_dry_ocs)
1356          CALL histwrite_phy(o_budg_dep_wet_ocs,     budg_dep_wet_ocs)
1357          CALL histwrite_phy(o_budg_dep_dry_so2,     budg_dep_dry_so2)
1358          CALL histwrite_phy(o_budg_dep_wet_so2,     budg_dep_wet_so2)
1359          CALL histwrite_phy(o_budg_dep_dry_h2so4,   budg_dep_dry_h2so4)
1360          CALL histwrite_phy(o_budg_dep_wet_h2so4,   budg_dep_wet_h2so4)
1361          CALL histwrite_phy(o_budg_dep_dry_part,    budg_dep_dry_part)
1362          CALL histwrite_phy(o_budg_dep_wet_part,    budg_dep_wet_part)
1363          CALL histwrite_phy(o_budg_emi_ocs,         budg_emi_ocs)
1364          CALL histwrite_phy(o_budg_emi_so2,         budg_emi_so2)
1365          CALL histwrite_phy(o_budg_emi_h2so4,       budg_emi_h2so4)
1366          CALL histwrite_phy(o_budg_emi_part,        budg_emi_part)
1367          CALL histwrite_phy(o_budg_ocs_to_so2,      budg_ocs_to_so2)
1368          CALL histwrite_phy(o_budg_so2_to_h2so4,    budg_so2_to_h2so4)
1369          CALL histwrite_phy(o_budg_h2so4_to_part,   budg_h2so4_to_part)
1370          CALL histwrite_phy(o_budg_sed_part,        budg_sed_part)
1371          CALL histwrite_phy(o_surf_PM25_sulf, surf_PM25_sulf)
1372          CALL histwrite_phy(o_vsed_aer, vsed_aer)
1373          CALL histwrite_phy(o_f_r_wet, f_r_wet)
1374          CALL histwrite_phy(o_ext_strat_550, tau_strat_550)
1375          CALL histwrite_phy(o_ext_strat_1020, tau_strat_1020)
1376          CALL histwrite_phy(o_tau_strat_550, tausum_strat(:,1))
1377          CALL histwrite_phy(o_tau_strat_1020, tausum_strat(:,2))
1378       ENDIF
1379#endif
1380       IF (ok_ade) THEN
1381          CALL histwrite_phy(o_topswad, topswad_aero*swradcorr)
1382          CALL histwrite_phy(o_topswad0, topswad0_aero*swradcorr)
1383          CALL histwrite_phy(o_solswad, solswad_aero*swradcorr)
1384          CALL histwrite_phy(o_solswad0, solswad0_aero*swradcorr)
1385          IF (type_trac .ne. 'inca') THEN
1386             IF (config_inca .ne. 'aeNP') THEN
1387                CALL histwrite_phy(o_toplwad, toplwad_aero)
1388                CALL histwrite_phy(o_toplwad0, toplwad0_aero)
1389                CALL histwrite_phy(o_sollwad, sollwad_aero)
1390                CALL histwrite_phy(o_sollwad0, sollwad0_aero)
1391             ENDIF
1392          ENDIF
1393          !====MS forcing diagnostics
1394          IF (new_aod) THEN
1395             zx_tmp_fi2d(:)=topsw_aero(:,1)*swradcorr(:)
1396             CALL histwrite_phy(o_swtoaas_nat,zx_tmp_fi2d)
1397             zx_tmp_fi2d(:)=solsw_aero(:,1)*swradcorr(:)
1398             CALL histwrite_phy(o_swsrfas_nat,zx_tmp_fi2d)
1399             zx_tmp_fi2d(:)=topsw0_aero(:,1)*swradcorr(:)
1400             CALL histwrite_phy(o_swtoacs_nat,zx_tmp_fi2d)
1401             zx_tmp_fi2d(:)=solsw0_aero(:,1)*swradcorr(:)
1402             CALL histwrite_phy(o_swsrfcs_nat,zx_tmp_fi2d)
1403             !ant
1404             zx_tmp_fi2d(:)=topsw_aero(:,2)*swradcorr(:)
1405             CALL histwrite_phy(o_swtoaas_ant,zx_tmp_fi2d)
1406             zx_tmp_fi2d(:)=solsw_aero(:,2)*swradcorr(:)
1407             CALL histwrite_phy(o_swsrfas_ant,zx_tmp_fi2d)
1408             zx_tmp_fi2d(:)=topsw0_aero(:,2)*swradcorr(:)
1409             CALL histwrite_phy(o_swtoacs_ant,zx_tmp_fi2d)
1410             zx_tmp_fi2d(:)=solsw0_aero(:,2)*swradcorr(:)
1411             CALL histwrite_phy(o_swsrfcs_ant,zx_tmp_fi2d)
1412             !cf
1413             IF (.not. aerosol_couple) THEN
1414                zx_tmp_fi2d(:)=topswcf_aero(:,1)*swradcorr(:)
1415                CALL histwrite_phy(o_swtoacf_nat,zx_tmp_fi2d)
1416                zx_tmp_fi2d(:)=solswcf_aero(:,1)*swradcorr(:)
1417                CALL histwrite_phy(o_swsrfcf_nat,zx_tmp_fi2d)
1418                zx_tmp_fi2d(:)=topswcf_aero(:,2)*swradcorr(:)
1419                CALL histwrite_phy(o_swtoacf_ant,zx_tmp_fi2d)
1420                zx_tmp_fi2d(:)=solswcf_aero(:,2)*swradcorr(:)
1421                CALL histwrite_phy(o_swsrfcf_ant,zx_tmp_fi2d)
1422                zx_tmp_fi2d(:)=topswcf_aero(:,3)*swradcorr(:)
1423                CALL histwrite_phy(o_swtoacf_zero,zx_tmp_fi2d)
1424                zx_tmp_fi2d(:)=solswcf_aero(:,3)*swradcorr(:)
1425                CALL histwrite_phy(o_swsrfcf_zero,zx_tmp_fi2d)
1426             ENDIF
1427          ENDIF ! new_aod
1428          !====MS forcing diagnostics
1429       ENDIF
1430       IF (ok_aie) THEN
1431          CALL histwrite_phy(o_topswai, topswai_aero*swradcorr)
1432          CALL histwrite_phy(o_toplwai, toplwai_aero*swradcorr)
1433          CALL histwrite_phy(o_solswai, solswai_aero*swradcorr)
1434          CALL histwrite_phy(o_sollwai, sollwai_aero*swradcorr)
1435       ENDIF
1436       IF (flag_aerosol.GT.0.AND.ok_cdnc) THEN
1437          CALL histwrite_phy(o_scdnc, scdnc)
1438          CALL histwrite_phy(o_cldncl, cldncl)
1439          CALL histwrite_phy(o_reffclws, reffclws)
1440          CALL histwrite_phy(o_reffclwc, reffclwc)
1441          CALL histwrite_phy(o_cldnvi, cldnvi)
1442          CALL histwrite_phy(o_lcc, lcc)
1443          CALL histwrite_phy(o_lcc3d, lcc3d)
1444          CALL histwrite_phy(o_lcc3dcon, lcc3dcon)
1445          CALL histwrite_phy(o_lcc3dstra, lcc3dstra)
1446          CALL histwrite_phy(o_icc3dcon, icc3dcon)
1447          CALL histwrite_phy(o_icc3dstra, icc3dstra)
1448          CALL histwrite_phy(o_cldicemxrat, zfice)
1449          zx_tmp_fi3d(:,:)=1-zfice(:,:)
1450          CALL histwrite_phy(o_cldwatmxrat, zx_tmp_fi3d)
1451          CALL histwrite_phy(o_reffclwtop, reffclwtop)
1452       ENDIF
1453       ! Champs 3D:
1454       IF (ok_ade .OR. ok_aie) then
1455          CALL histwrite_phy(o_ec550aer, ec550aer)
1456       ENDIF
1457       CALL histwrite_phy(o_lwcon, flwc)
1458       CALL histwrite_phy(o_iwcon, fiwc)
1459       CALL histwrite_phy(o_temp, t_seri)
1460       CALL histwrite_phy(o_theta, theta)
1461       CALL histwrite_phy(o_ovapinit, qx(:,:,ivap))
1462       CALL histwrite_phy(o_ovap, q_seri)
1463       CALL histwrite_phy(o_oliq, ql_seri)
1464       CALL histwrite_phy(o_ocond, ql_seri+qs_seri)
1465       CALL histwrite_phy(o_geop, zphi)
1466       CALL histwrite_phy(o_vitu, u_seri)
1467       CALL histwrite_phy(o_vitv, v_seri)
1468       CALL histwrite_phy(o_vitw, omega)
1469       CALL histwrite_phy(o_pres, pplay)
1470       CALL histwrite_phy(o_paprs, paprs(:,1:klev))
1471       CALL histwrite_phy(o_zfull,zphi/RG)
1472
1473#ifdef CPP_XIOS
1474!solbnd begin
1475#ifdef CPP_RRTM
1476      IF (iflag_rrtm.EQ.1) THEN
1477       IF (vars_defined) THEN
1478        DO ISW=1, NSW
1479          zx_tmp_fi3dsp(:,ISW) = swdn(:,klevp1)*swradcorr(:)*RSUN(ISW)
1480        ENDDO
1481        CALL histwrite_phy(o_solbnd, zx_tmp_fi3dsp)
1482       ENDIF
1483      ENDIF
1484#endif
1485!solbnd end
1486#endif
1487
1488       IF (flag_aerosol_strat.EQ.2) THEN
1489         CALL histwrite_phy(o_stratomask, stratomask)
1490       ENDIF
1491     
1492       IF (vars_defined)  THEN
1493        zx_tmp_fi3d(:,1)= pphis(:)/RG
1494        DO k = 2, klev
1495         DO i = 1, klon
1496            zx_tmp_fi3d(i,k) = zphi(i,k-1)/RG + &
1497                          (zphi(i,k)-zphi(i,k-1))/RG * &
1498                          (paprs(i,k)-pplay(i,k-1))/(pplay(i,k)-pplay(i,k-1))
1499         ENDDO
1500        ENDDO
1501       ENDIF
1502       CALL histwrite_phy(o_zhalf, zx_tmp_fi3d)
1503       CALL histwrite_phy(o_rneb, cldfra)
1504       CALL histwrite_phy(o_rnebcon, rnebcon)
1505       CALL histwrite_phy(o_rnebls, rneb)
1506       CALL histwrite_phy(o_rneblsvol, rneblsvol)
1507       IF (vars_defined)  THEN
1508          DO k=1, klev
1509             DO i=1, klon
1510                zx_tmp_fi3d(i,k)=cldfra(i,k)*JrNt(i)
1511             ENDDO
1512          ENDDO
1513       ENDIF
1514       CALL histwrite_phy(o_rnebjn, zx_tmp_fi3d)
1515       CALL histwrite_phy(o_rhum, zx_rh)
1516       CALL histwrite_phy(o_ozone, &
1517            wo(:, :, 1) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
1518
1519       IF (read_climoz == 2) THEN
1520          CALL histwrite_phy(o_ozone_light, &
1521               wo(:, :, 2) * dobson_u * 1e3 / zmasse / rmo3 * rmd)
1522       ENDIF
1523
1524       CALL histwrite_phy(o_duphy, d_u)
1525
1526       CALL histwrite_phy(o_dtphy, d_t)
1527
1528       CALL histwrite_phy(o_dqphy,  d_qx(:,:,ivap))
1529       CALL water_int(klon,klev,d_qx(:,:,ivap),zmasse,zx_tmp_fi2d)
1530       CALL histwrite_phy(o_dqphy2d,  zx_tmp_fi2d)
1531
1532       CALL histwrite_phy(o_dqlphy,  d_qx(:,:,iliq))
1533       CALL water_int(klon,klev,d_qx(:,:,iliq),zmasse,zx_tmp_fi2d)
1534       CALL histwrite_phy(o_dqlphy2d,  zx_tmp_fi2d)
1535
1536       IF (nqo.EQ.3) THEN
1537       CALL histwrite_phy(o_dqsphy,  d_qx(:,:,isol))
1538       CALL water_int(klon,klev,d_qx(:,:,isol),zmasse,zx_tmp_fi2d)
1539       CALL histwrite_phy(o_dqsphy2d,  zx_tmp_fi2d)
1540       ELSE
1541       zx_tmp_fi3d=0.0
1542       CALL histwrite_phy(o_dqsphy,  zx_tmp_fi3d)
1543       zx_tmp_fi2d=0.0
1544       CALL histwrite_phy(o_dqsphy2d,  zx_tmp_fi2d)
1545       ENDIF
1546
1547       DO nsrf=1, nbsrf
1548          IF (vars_defined) zx_tmp_fi2d(1 : klon) = falb1( 1 : klon, nsrf)
1549          CALL histwrite_phy(o_albe_srf(nsrf), zx_tmp_fi2d)
1550          IF (vars_defined) zx_tmp_fi2d(1 : klon) = z0m( 1 : klon, nsrf)
1551          CALL histwrite_phy(o_z0m_srf(nsrf), zx_tmp_fi2d)
1552          IF (vars_defined) zx_tmp_fi2d(1 : klon) = z0h( 1 : klon, nsrf)
1553          CALL histwrite_phy(o_z0h_srf(nsrf), zx_tmp_fi2d)
1554          IF (vars_defined) zx_tmp_fi2d(1 : klon) = agesno( 1 : klon, nsrf)
1555          CALL histwrite_phy(o_ages_srf(nsrf), zx_tmp_fi2d)
1556          IF (vars_defined) zx_tmp_fi2d(1 : klon) = snow( 1 : klon, nsrf)
1557          CALL histwrite_phy(o_snow_srf(nsrf), zx_tmp_fi2d)
1558       ENDDO !nsrf=1, nbsrf
1559       CALL histwrite_phy(o_alb1, albsol1)
1560       CALL histwrite_phy(o_alb2, albsol2)
1561       !FH Sorties pour la couche limite
1562       IF (iflag_pbl>1) THEN
1563          zx_tmp_fi3d=0.
1564          IF (vars_defined) THEN
1565             DO nsrf=1,nbsrf
1566                DO k=1,klev
1567                   zx_tmp_fi3d(:,k)=zx_tmp_fi3d(:,k) &
1568                        +pctsrf(:,nsrf)*pbl_tke(:,k,nsrf)
1569                ENDDO
1570             ENDDO
1571          ENDIF
1572          CALL histwrite_phy(o_tke, zx_tmp_fi3d)
1573
1574          CALL histwrite_phy(o_tke_max, zx_tmp_fi3d)
1575       ENDIF
1576
1577       CALL histwrite_phy(o_kz, coefh(:,:,is_ave))
1578
1579       CALL histwrite_phy(o_kz_max, coefh(:,:,is_ave))
1580
1581       CALL histwrite_phy(o_clwcon, clwcon0)
1582       CALL histwrite_phy(o_dtdyn, d_t_dyn)
1583
1584       CALL histwrite_phy(o_dqdyn, d_q_dyn)
1585
1586       CALL histwrite_phy(o_dqdyn2d,d_q_dyn2d)
1587
1588       CALL histwrite_phy(o_dqldyn, d_ql_dyn)
1589
1590       CALL histwrite_phy(o_dqldyn2d, d_ql_dyn2d)
1591
1592       CALL histwrite_phy(o_dqsdyn, d_qs_dyn)
1593
1594       CALL histwrite_phy(o_dqsdyn2d, d_qs_dyn2d)
1595
1596       CALL histwrite_phy(o_dudyn, d_u_dyn)
1597       CALL histwrite_phy(o_dvdyn, d_v_dyn)
1598
1599       IF (vars_defined) THEN
1600          zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys
1601       ENDIF
1602       CALL histwrite_phy(o_dtcon, zx_tmp_fi3d)
1603       if(iflag_thermals.eq.0)then
1604          IF (vars_defined) THEN
1605             zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
1606                  d_t_ajsb(1:klon,1:klev)/pdtphys
1607          ENDIF
1608          CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
1609       else if(iflag_thermals.ge.1.and.iflag_wake.EQ.1)then
1610          IF (vars_defined) THEN
1611             zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
1612                  d_t_ajs(1:klon,1:klev)/pdtphys + &
1613                  d_t_wake(1:klon,1:klev)/pdtphys
1614          ENDIF
1615          CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
1616       endif
1617       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_con(1:klon,1:klev)/pdtphys
1618       CALL histwrite_phy(o_ducon, zx_tmp_fi3d)
1619       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_con(1:klon,1:klev)/pdtphys
1620       CALL histwrite_phy(o_dvcon, zx_tmp_fi3d)
1621       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
1622       CALL histwrite_phy(o_dqcon, zx_tmp_fi3d)
1623       CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1624       CALL histwrite_phy(o_dqcon2d, zx_tmp_fi2d)
1625
1626       IF (iflag_thermals.EQ.0) THEN
1627          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys
1628          CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
1629       ELSE IF (iflag_thermals.GE.1.AND.iflag_wake.EQ.1) THEN
1630          IF (vars_defined) THEN
1631             zx_tmp_fi3d(1:klon,1:klev)=d_q_con(1:klon,1:klev)/pdtphys + &
1632                  d_q_ajs(1:klon,1:klev)/pdtphys + &
1633                  d_q_wake(1:klon,1:klev)/pdtphys
1634          ENDIF
1635          CALL histwrite_phy(o_tnhusc, zx_tmp_fi3d)
1636       ENDIF
1637
1638       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lsc(1:klon,1:klev)/pdtphys
1639       CALL histwrite_phy(o_dtlsc, zx_tmp_fi3d)
1640       IF (vars_defined) zx_tmp_fi3d(1:klon, 1:klev)=(d_t_lsc(1:klon,1:klev)+ &
1641            d_t_eva(1:klon,1:klev))/pdtphys
1642       CALL histwrite_phy(o_dtlschr, zx_tmp_fi3d)
1643       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys
1644       CALL histwrite_phy(o_dqlsc, zx_tmp_fi3d)
1645       CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1646       CALL histwrite_phy(o_dqlsc2d, zx_tmp_fi2d)
1647       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=beta_prec(1:klon,1:klev)
1648       CALL histwrite_phy(o_beta_prec, zx_tmp_fi3d)
1649!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1650       ! Sorties specifiques a la separation thermiques/non thermiques
1651       IF (iflag_thermals>=1) THEN
1652          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lscth(1:klon,1:klev)/pdtphys
1653          CALL histwrite_phy(o_dtlscth, zx_tmp_fi3d)
1654          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lscst(1:klon,1:klev)/pdtphys
1655          CALL histwrite_phy(o_dtlscst, zx_tmp_fi3d)
1656          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lscth(1:klon,1:klev)/pdtphys
1657          CALL histwrite_phy(o_dqlscth, zx_tmp_fi3d)
1658          CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1659          CALL histwrite_phy(o_dqlscth2d, zx_tmp_fi2d)
1660          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_lscst(1:klon,1:klev)/pdtphys
1661          CALL histwrite_phy(o_dqlscst, zx_tmp_fi3d)
1662          CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1663          CALL histwrite_phy(o_dqlscst2d, zx_tmp_fi2d)
1664          CALL histwrite_phy(o_plulth, plul_th)
1665          CALL histwrite_phy(o_plulst, plul_st)
1666          IF (vars_defined) THEN
1667             do i=1,klon
1668                zx_tmp_fi2d(1:klon)=lmax_th(:)
1669             enddo
1670          ENDIF
1671          CALL histwrite_phy(o_lmaxth, zx_tmp_fi2d)
1672          IF (vars_defined) THEN
1673             DO k=1,klev
1674                DO i=1,klon
1675                   IF (ptconvth(i,k)) THEN
1676                      zx_tmp_fi3d(i,k)=1.
1677                   ELSE
1678                      zx_tmp_fi3d(i,k)=0.
1679                   ENDIF
1680                ENDDO
1681             ENDDO
1682          ENDIF
1683          CALL histwrite_phy(o_ptconvth, zx_tmp_fi3d)
1684       ENDIF ! iflag_thermals>=1
1685!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1686       zpt_conv = 0.
1687       WHERE (ptconv) zpt_conv = 1.
1688       CALL histwrite_phy(o_ptconv, zpt_conv)
1689!!       IF (vars_defined)         zx_tmp_fi2d=float(itau_con)/float(itap)
1690!!       CALL histwrite_phy(o_ftime_con, zx_tmp_fi2d)
1691       IF (vars_defined) THEN
1692          zpt_conv2d(:) = 0.
1693          DO k=1,klev
1694            WHERE (ptconv(:,k)) zpt_conv2d(:) = 1.
1695          ENDDO
1696       ENDIF
1697       CALL histwrite_phy(o_ftime_deepcv, zpt_conv2d)
1698       IF (vars_defined) THEN
1699          zx_tmp_fi2d(:) = 0.
1700          DO k=1,klev
1701            WHERE (ptconvth(:,k)) zx_tmp_fi2d(:) = 1.
1702          ENDDO
1703       ENDIF
1704       CALL histwrite_phy(o_ftime_th, zx_tmp_fi2d)
1705       IF (vars_defined) THEN
1706           zx_tmp_fi2d(:) = max(zx_tmp_fi2d(:),zpt_conv2d(:))
1707       ENDIF
1708       CALL histwrite_phy(o_ftime_con, zx_tmp_fi2d)
1709!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1710       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_vdf(1:klon,1:klev)/pdtphys
1711       CALL histwrite_phy(o_dtvdf, zx_tmp_fi3d)
1712       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_diss(1:klon,1:klev)/pdtphys
1713       CALL histwrite_phy(o_dtdis, zx_tmp_fi3d)
1714       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_vdf(1:klon,1:klev)/pdtphys
1715       CALL histwrite_phy(o_dqvdf, zx_tmp_fi3d)
1716       CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1717       CALL histwrite_phy(o_dqvdf2d, zx_tmp_fi2d)
1718       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_eva(1:klon,1:klev)/pdtphys
1719       CALL histwrite_phy(o_dteva, zx_tmp_fi3d)
1720       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_eva(1:klon,1:klev)/pdtphys
1721       CALL histwrite_phy(o_dqeva, zx_tmp_fi3d)
1722       CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1723       CALL histwrite_phy(o_dqeva2d, zx_tmp_fi2d)
1724       CALL histwrite_phy(o_ratqs, ratqs)
1725       IF (vars_defined) THEN
1726          zx_tmp_fi3d(1:klon,1:klev)=d_t_ajs(1:klon,1:klev)/pdtphys - &
1727               d_t_ajsb(1:klon,1:klev)/pdtphys
1728       ENDIF
1729       CALL histwrite_phy(o_dtthe, zx_tmp_fi3d)
1730       IF (vars_defined) THEN
1731          zx_tmp_fi3d(1:klon,1:klev)=d_u_ajs(1:klon,1:klev)/pdtphys
1732       ENDIF
1733       CALL histwrite_phy(o_duthe, zx_tmp_fi3d)
1734       IF (vars_defined) THEN
1735          zx_tmp_fi3d(1:klon,1:klev)=d_v_ajs(1:klon,1:klev)/pdtphys
1736       ENDIF
1737       CALL histwrite_phy(o_dvthe, zx_tmp_fi3d)
1738
1739       IF (iflag_thermals>=1) THEN
1740          ! Pour l instant 0 a y reflichir pour les thermiques
1741          ! regroupe avec ftime_deepcv et ftime_con
1742          !!zx_tmp_fi2d=0.
1743          !!CALL histwrite_phy(o_ftime_th, zx_tmp_fi2d)
1744          CALL histwrite_phy(o_f_th, fm_therm)
1745          CALL histwrite_phy(o_e_th, entr_therm)
1746          CALL histwrite_phy(o_w_th, zw2)
1747          CALL histwrite_phy(o_q_th, zqasc)
1748          CALL histwrite_phy(o_a_th, fraca)
1749          CALL histwrite_phy(o_cloudth_sth, cloudth_sth)
1750          CALL histwrite_phy(o_cloudth_senv, cloudth_senv)
1751          CALL histwrite_phy(o_cloudth_sigmath, cloudth_sigmath)
1752          CALL histwrite_phy(o_cloudth_sigmaenv, cloudth_sigmaenv)
1753          CALL histwrite_phy(o_d_th, detr_therm)
1754          CALL histwrite_phy(o_f0_th, f0)
1755          CALL histwrite_phy(o_zmax_th, zmax_th)
1756          IF (vars_defined) THEN
1757             zx_tmp_fi3d(1:klon,1:klev)=d_q_ajs(1:klon,1:klev)/pdtphys - &
1758                  d_q_ajsb(1:klon,1:klev)/pdtphys
1759          ENDIF
1760          CALL histwrite_phy(o_dqthe, zx_tmp_fi3d)
1761          CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1762          CALL histwrite_phy(o_dqthe2d, zx_tmp_fi2d)
1763       ENDIF !iflag_thermals
1764       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_ajsb(1:klon,1:klev)/pdtphys
1765       CALL histwrite_phy(o_dtajs, zx_tmp_fi3d)
1766       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_q_ajsb(1:klon,1:klev)/pdtphys
1767       CALL histwrite_phy(o_dqajs, zx_tmp_fi3d)
1768       CALL water_int(klon,klev,zx_tmp_fi3d,zmasse,zx_tmp_fi2d)
1769       CALL histwrite_phy(o_dqajs2d, zx_tmp_fi2d)
1770       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_swr(1:klon,1:klev)/pdtphys
1771       CALL histwrite_phy(o_dtswr, zx_tmp_fi3d)
1772       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_sw0(1:klon,1:klev)/pdtphys
1773       CALL histwrite_phy(o_dtsw0, zx_tmp_fi3d)
1774       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lwr(1:klon,1:klev)/pdtphys
1775       CALL histwrite_phy(o_dtlwr, zx_tmp_fi3d)
1776       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lw0(1:klon,1:klev)/pdtphys
1777       CALL histwrite_phy(o_dtlw0, zx_tmp_fi3d)
1778       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_ec(1:klon,1:klev)/pdtphys
1779       CALL histwrite_phy(o_dtec, zx_tmp_fi3d)
1780       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_vdf(1:klon,1:klev)/pdtphys
1781       CALL histwrite_phy(o_duvdf, zx_tmp_fi3d)
1782       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_vdf(1:klon,1:klev)/pdtphys
1783       CALL histwrite_phy(o_dvvdf, zx_tmp_fi3d)
1784       IF (ok_orodr) THEN
1785          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_oro(1:klon,1:klev)/pdtphys
1786          CALL histwrite_phy(o_duoro, zx_tmp_fi3d)
1787          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_oro(1:klon,1:klev)/pdtphys
1788          CALL histwrite_phy(o_dvoro, zx_tmp_fi3d)
1789          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_oro(1:klon,1:klev)/pdtphys
1790          CALL histwrite_phy(o_dtoro, zx_tmp_fi3d)
1791       ENDIF
1792       IF (ok_orolf) THEN
1793          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_lif(1:klon,1:klev)/pdtphys
1794          CALL histwrite_phy(o_dulif, zx_tmp_fi3d)
1795
1796          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_lif(1:klon,1:klev)/pdtphys
1797          CALL histwrite_phy(o_dvlif, zx_tmp_fi3d)
1798
1799          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_lif(1:klon,1:klev)/pdtphys
1800          CALL histwrite_phy(o_dtlif, zx_tmp_fi3d)
1801       ENDIF
1802
1803       IF (ok_hines) THEN
1804          CALL histwrite_phy(o_du_gwd_hines, du_gwd_hines/pdtphys)
1805          CALL histwrite_phy(o_dv_gwd_hines, dv_gwd_hines/pdtphys)
1806          IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_hin(1:klon,1:klev)/pdtphys
1807          CALL histwrite_phy(o_dthin, zx_tmp_fi3d)
1808          CALL histwrite_phy(o_ustr_gwd_hines, zustr_gwd_hines)
1809          CALL histwrite_phy(o_vstr_gwd_hines, zvstr_gwd_hines)
1810       ENDIF
1811
1812       IF (.not. ok_hines .and. ok_gwd_rando) THEN
1813          CALL histwrite_phy(o_du_gwd_front, du_gwd_front / pdtphys)
1814          CALL histwrite_phy(o_dv_gwd_front, dv_gwd_front / pdtphys)
1815          CALL histwrite_phy(o_ustr_gwd_front, zustr_gwd_front)
1816          CALL histwrite_phy(o_vstr_gwd_front, zvstr_gwd_front)
1817       ENDIF
1818
1819       IF (ok_gwd_rando) THEN
1820          CALL histwrite_phy(o_du_gwd_rando, du_gwd_rando / pdtphys)
1821          CALL histwrite_phy(o_dv_gwd_rando, dv_gwd_rando / pdtphys)
1822          CALL histwrite_phy(o_ustr_gwd_rando, zustr_gwd_rando)
1823          CALL histwrite_phy(o_vstr_gwd_rando, zvstr_gwd_rando)
1824          CALL histwrite_phy(o_east_gwstress, east_gwstress )
1825          CALL histwrite_phy(o_west_gwstress, west_gwstress )
1826       ENDIF
1827
1828       IF (ok_qch4) THEN
1829          CALL histwrite_phy(o_dqch4, d_q_ch4 / pdtphys)
1830       ENDIF
1831
1832       DO k=1, klevp1
1833         zx_tmp_fi3d1(:,k)=swup(:,k)*swradcorr(:)
1834       ENDDO
1835       CALL histwrite_phy(o_rsu, zx_tmp_fi3d1)
1836       DO k=1, klevp1
1837         zx_tmp_fi3d1(:,k)=swdn(:,k)*swradcorr(:)
1838       ENDDO
1839       CALL histwrite_phy(o_rsd, zx_tmp_fi3d1)
1840       DO k=1, klevp1
1841         zx_tmp_fi3d1(:,k)=swup0(:,k)*swradcorr(:)
1842       ENDDO
1843       CALL histwrite_phy(o_rsucs, zx_tmp_fi3d1)
1844       DO k=1, klevp1
1845         zx_tmp_fi3d1(:,k)=swupc0(:,k)*swradcorr(:)
1846       ENDDO
1847       CALL histwrite_phy(o_rsucsaf, zx_tmp_fi3d1)
1848       DO k=1, klevp1
1849         zx_tmp_fi3d1(:,k)=swdn0(:,k)*swradcorr(:)
1850       ENDDO
1851       CALL histwrite_phy(o_rsdcs, zx_tmp_fi3d1)
1852       DO k=1, klevp1
1853         zx_tmp_fi3d1(:,k)=swdnc0(:,k)*swradcorr(:)
1854       ENDDO
1855       CALL histwrite_phy(o_rsdcsaf, zx_tmp_fi3d1)
1856
1857       CALL histwrite_phy(o_rlu, lwup)
1858       CALL histwrite_phy(o_rld, lwdn)
1859       CALL histwrite_phy(o_rlucs, lwup0)
1860       CALL histwrite_phy(o_rldcs, lwdn0)
1861
1862       IF (vars_defined) THEN
1863          zx_tmp_fi3d(1:klon,1:klev)=d_t(1:klon,1:klev)+ &
1864               d_t_dyn(1:klon,1:klev)
1865       ENDIF
1866       CALL histwrite_phy(o_tnt, zx_tmp_fi3d)
1867
1868       IF (vars_defined) THEN
1869          zx_tmp_fi3d(1:klon,1:klev)=d_t_swr(1:klon,1:klev)/pdtphys + &
1870               d_t_lwr(1:klon,1:klev)/pdtphys
1871       ENDIF
1872       CALL histwrite_phy(o_tntr, zx_tmp_fi3d)
1873       IF (vars_defined) THEN
1874          zx_tmp_fi3d(1:klon,1:klev)= (d_t_lsc(1:klon,1:klev)+ &
1875               d_t_eva(1:klon,1:klev)+ &
1876               d_t_vdf(1:klon,1:klev))/pdtphys
1877       ENDIF
1878       CALL histwrite_phy(o_tntscpbl, zx_tmp_fi3d)
1879       IF (vars_defined) THEN
1880          zx_tmp_fi3d(1:klon,1:klev)=d_qx(1:klon,1:klev,ivap)+ &
1881               d_q_dyn(1:klon,1:klev)
1882       ENDIF
1883       CALL histwrite_phy(o_tnhus, zx_tmp_fi3d)
1884       IF (vars_defined) THEN
1885          zx_tmp_fi3d(1:klon,1:klev)=d_q_lsc(1:klon,1:klev)/pdtphys+ &
1886               d_q_eva(1:klon,1:klev)/pdtphys
1887       ENDIF
1888       CALL histwrite_phy(o_tnhusscpbl, zx_tmp_fi3d)
1889       CALL histwrite_phy(o_evu, coefm(:,:,is_ave))
1890       IF (vars_defined) THEN
1891          zx_tmp_fi3d(1:klon,1:klev)=q_seri(1:klon,1:klev)+ &
1892               ql_seri(1:klon,1:klev)
1893       ENDIF
1894       CALL histwrite_phy(o_h2o, zx_tmp_fi3d)
1895       IF (iflag_con >= 3) THEN
1896          IF (vars_defined) THEN
1897             zx_tmp_fi3d(1:klon,1:klev)=-1 * (dnwd(1:klon,1:klev)+ &
1898                  dnwd0(1:klon,1:klev))
1899          ENDIF
1900          CALL histwrite_phy(o_mcd, zx_tmp_fi3d)
1901          IF (vars_defined) THEN
1902             zx_tmp_fi3d(1:klon,1:klev)=upwd(1:klon,1:klev) + &
1903                  dnwd(1:klon,1:klev)+ dnwd0(1:klon,1:klev)
1904          ENDIF
1905          CALL histwrite_phy(o_dmc, zx_tmp_fi3d)
1906       ELSE IF (iflag_con == 2) THEN
1907          CALL histwrite_phy(o_mcd,  pmfd)
1908          CALL histwrite_phy(o_dmc,  pmfu + pmfd)
1909       ENDIF
1910       CALL histwrite_phy(o_ref_liq, ref_liq)
1911       CALL histwrite_phy(o_ref_ice, ref_ice)
1912!
1913       IF (ok_4xCO2atm) THEN
1914          IF (vars_defined) zx_tmp_fi2d(:) = swupp(:,klevp1)*swradcorr(:)
1915          CALL histwrite_phy(o_rsut4co2, zx_tmp_fi2d)
1916          IF (vars_defined) zx_tmp_fi2d(:) = lwupp(:,klevp1)
1917          CALL histwrite_phy(o_rlut4co2, zx_tmp_fi2d)
1918          IF (vars_defined) zx_tmp_fi2d(:) = swup0p(:,klevp1)*swradcorr(:)
1919          CALL histwrite_phy(o_rsutcs4co2, zx_tmp_fi2d)
1920          IF (vars_defined) zx_tmp_fi2d(:) = lwup0p(:,klevp1)
1921          CALL histwrite_phy(o_rlutcs4co2, zx_tmp_fi2d)
1922          DO k=1, klevp1
1923            zx_tmp_fi3d1(:,k)=swupp(:,k)*swradcorr(:)
1924          ENDDO
1925          CALL histwrite_phy(o_rsu4co2, zx_tmp_fi3d1)
1926          DO k=1, klevp1
1927            zx_tmp_fi3d1(:,k)=swup0p(:,k)*swradcorr(:)
1928          ENDDO
1929          CALL histwrite_phy(o_rsucs4co2, zx_tmp_fi3d1)
1930          DO k=1, klevp1
1931            zx_tmp_fi3d1(:,k)=swdnp(:,k)*swradcorr(:)
1932          ENDDO
1933          CALL histwrite_phy(o_rsd4co2, zx_tmp_fi3d1)
1934          DO k=1, klevp1
1935            zx_tmp_fi3d1(:,k)=swdn0p(:,k)*swradcorr(:)
1936          ENDDO
1937          CALL histwrite_phy(o_rsdcs4co2, zx_tmp_fi3d1)
1938          CALL histwrite_phy(o_rlu4co2, lwupp)
1939          CALL histwrite_phy(o_rlucs4co2, lwup0p)
1940          CALL histwrite_phy(o_rld4co2, lwdnp)
1941          CALL histwrite_phy(o_rldcs4co2, lwdn0p)
1942       ENDIF !ok_4xCO2atm
1943!!!!!!!!!!!! Sorties niveaux de pression NMC !!!!!!!!!!!!!!!!!!!!
1944#ifdef CPP_IOIPSL
1945#ifndef CPP_XIOS
1946  IF (.NOT.ok_all_xml) THEN
1947       ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
1948       ! Champs interpolles sur des niveaux de pression
1949       missing_val=missing_val_nf90
1950       DO iff=7, nfiles-1 !--OB: here we deal with files 7,8,9
1951
1952          CALL histwrite_phy(o_tnondef,tnondef(:,:,iff-6),iff)
1953          CALL histwrite_phy(o_ta,twriteSTD(:,:,iff-6),iff)
1954          CALL histwrite_phy(o_zg,phiwriteSTD(:,:,iff-6),iff)
1955          CALL histwrite_phy(o_hus,qwriteSTD(:,:,iff-6),iff)
1956          CALL histwrite_phy(o_hur,rhwriteSTD(:,:,iff-6),iff)
1957          CALL histwrite_phy(o_ua,uwriteSTD(:,:,iff-6),iff)
1958          CALL histwrite_phy(o_va,vwriteSTD(:,:,iff-6),iff)
1959          CALL histwrite_phy(o_wap,wwriteSTD(:,:,iff-6),iff)
1960          IF (vars_defined) THEN
1961             DO k=1, nlevSTD
1962                DO i=1, klon
1963                   IF (tnondef(i,k,iff-6).NE.missing_val) THEN
1964                      IF (freq_outNMC(iff-6).LT.0) THEN
1965                         freq_moyNMC(iff-6)=(mth_len*un_jour)/freq_calNMC(iff-6)
1966                      ELSE
1967                         freq_moyNMC(iff-6)=freq_outNMC(iff-6)/freq_calNMC(iff-6)
1968                      ENDIF
1969                      zx_tmp_fi3d_STD(i,k) = (100.*tnondef(i,k,iff-6))/freq_moyNMC(iff-6)
1970                   ELSE
1971                      zx_tmp_fi3d_STD(i,k) = missing_val
1972                   ENDIF
1973                ENDDO
1974             ENDDO
1975          ENDIF
1976          CALL histwrite_phy(o_psbg,zx_tmp_fi3d_STD,iff)
1977          IF (vars_defined) THEN
1978             DO k=1, nlevSTD
1979                DO i=1, klon
1980                   IF (O3sumSTD(i,k,iff-6).NE.missing_val) THEN
1981                      zx_tmp_fi3d_STD(i,k) = O3sumSTD(i,k,iff-6) * 1.e+9
1982                   ELSE
1983                      zx_tmp_fi3d_STD(i,k) = missing_val
1984                   ENDIF
1985                ENDDO
1986             ENDDO !k=1, nlevSTD
1987          ENDIF
1988          CALL histwrite_phy(o_tro3,zx_tmp_fi3d_STD,iff)
1989          IF (read_climoz == 2) THEN
1990             IF (vars_defined) THEN
1991                DO k=1, nlevSTD
1992                   DO i=1, klon
1993                      IF (O3daysumSTD(i,k,iff-6).NE.missing_val) THEN
1994                         zx_tmp_fi3d_STD(i,k) = O3daysumSTD(i,k,iff-6) * 1.e+9
1995                      ELSE
1996                         zx_tmp_fi3d_STD(i,k) = missing_val
1997                      ENDIF
1998                   ENDDO
1999                ENDDO !k=1, nlevSTD
2000             ENDIF
2001             CALL histwrite_phy(o_tro3_daylight,zx_tmp_fi3d_STD,iff)
2002          endif
2003          CALL histwrite_phy(o_uxv,uvsumSTD(:,:,iff-6),iff)
2004          CALL histwrite_phy(o_vxq,vqsumSTD(:,:,iff-6),iff)
2005          CALL histwrite_phy(o_vxT,vTsumSTD(:,:,iff-6),iff)
2006          CALL histwrite_phy(o_wxq,wqsumSTD(:,:,iff-6),iff)
2007          CALL histwrite_phy(o_vxphi,vphisumSTD(:,:,iff-6),iff)
2008          CALL histwrite_phy(o_wxT,wTsumSTD(:,:,iff-6),iff)
2009          CALL histwrite_phy(o_uxu,u2sumSTD(:,:,iff-6),iff)
2010          CALL histwrite_phy(o_vxv,v2sumSTD(:,:,iff-6),iff)
2011          CALL histwrite_phy(o_TxT,T2sumSTD(:,:,iff-6),iff)
2012       ENDDO !nfiles
2013  ENDIF
2014#endif
2015#endif
2016#ifdef CPP_XIOS
2017  IF (ok_all_xml) THEN
2018!      DO iff=7, nfiles
2019
2020!         CALL histwrite_phy(o_tnondef,tnondef(:,:,3))
2021          CALL histwrite_phy(o_ta,tlevSTD(:,:))
2022          CALL histwrite_phy(o_zg,philevSTD(:,:))
2023          CALL histwrite_phy(o_hus,qlevSTD(:,:))
2024          CALL histwrite_phy(o_hur,rhlevSTD(:,:))
2025          CALL histwrite_phy(o_ua,ulevSTD(:,:))
2026          CALL histwrite_phy(o_va,vlevSTD(:,:))
2027          CALL histwrite_phy(o_wap,wlevSTD(:,:))
2028!         IF (vars_defined) THEN
2029!            DO k=1, nlevSTD
2030!               DO i=1, klon
2031!                  IF (tnondef(i,k,3).NE.missing_val) THEN
2032!                     IF (freq_outNMC(iff-6).LT.0) THEN
2033!                        freq_moyNMC(iff-6)=(mth_len*un_jour)/freq_calNMC(iff-6)
2034!                     ELSE
2035!                        freq_moyNMC(iff-6)=freq_outNMC(iff-6)/freq_calNMC(iff-6)
2036!                     ENDIF
2037!                     zx_tmp_fi3d_STD(i,k) = (100.*tnondef(i,k,3))/freq_moyNMC(iff-6)
2038!                  ELSE
2039!                     zx_tmp_fi3d_STD(i,k) = missing_val
2040!                  ENDIF
2041!               ENDDO
2042!            ENDDO
2043!         ENDIF
2044!         CALL histwrite_phy(o_psbg,zx_tmp_fi3d_STD)
2045          IF (vars_defined) THEN
2046             DO k=1, nlevSTD
2047                DO i=1, klon
2048                   IF (O3STD(i,k).NE.missing_val) THEN
2049                      zx_tmp_fi3d_STD(i,k) = O3STD(i,k) * 1.e+9
2050                   ELSE
2051                      zx_tmp_fi3d_STD(i,k) = missing_val
2052                   ENDIF
2053                ENDDO
2054             ENDDO !k=1, nlevSTD
2055          ENDIF
2056          CALL histwrite_phy(o_tro3,zx_tmp_fi3d_STD)
2057          IF (read_climoz == 2) THEN
2058             IF (vars_defined) THEN
2059                DO k=1, nlevSTD
2060                   DO i=1, klon
2061                      IF (O3daySTD(i,k).NE.missing_val) THEN
2062                         zx_tmp_fi3d_STD(i,k) = O3daySTD(i,k) * 1.e+9
2063                      ELSE
2064                         zx_tmp_fi3d_STD(i,k) = missing_val
2065                      ENDIF
2066                   ENDDO
2067                ENDDO !k=1, nlevSTD
2068             ENDIF
2069             CALL histwrite_phy(o_tro3_daylight,zx_tmp_fi3d_STD)
2070          ENDIF
2071          CALL histwrite_phy(o_uxv,uvSTD(:,:))
2072          CALL histwrite_phy(o_vxq,vqSTD(:,:))
2073          CALL histwrite_phy(o_vxT,vTSTD(:,:))
2074          CALL histwrite_phy(o_wxq,wqSTD(:,:))
2075          CALL histwrite_phy(o_vxphi,vphiSTD(:,:))
2076          CALL histwrite_phy(o_wxT,wTSTD(:,:))
2077          CALL histwrite_phy(o_uxu,u2STD(:,:))
2078          CALL histwrite_phy(o_vxv,v2STD(:,:))
2079          CALL histwrite_phy(o_TxT,T2STD(:,:))
2080!      ENDDO !nfiles
2081  ENDIF
2082#endif
2083!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2084       IF (iflag_phytrac == 1 ) then
2085       IF (nqtot.GE.nqo+1) THEN
2086          DO iq=nqo+1, nqtot
2087            IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag') THEN
2088             !--3D fields
2089             CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo))
2090             CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo))
2091             CALL histwrite_phy(o_dtr_the(iq-nqo),d_tr_th(:,:,iq-nqo))
2092             CALL histwrite_phy(o_dtr_con(iq-nqo),d_tr_cv(:,:,iq-nqo))
2093             CALL histwrite_phy(o_dtr_lessi_impa(iq-nqo),d_tr_lessi_impa(:,:,iq-nqo))
2094             CALL histwrite_phy(o_dtr_lessi_nucl(iq-nqo),d_tr_lessi_nucl(:,:,iq-nqo))
2095             CALL histwrite_phy(o_dtr_insc(iq-nqo),d_tr_insc(:,:,iq-nqo))
2096             CALL histwrite_phy(o_dtr_bcscav(iq-nqo),d_tr_bcscav(:,:,iq-nqo))
2097             CALL histwrite_phy(o_dtr_evapls(iq-nqo),d_tr_evapls(:,:,iq-nqo))
2098             CALL histwrite_phy(o_dtr_ls(iq-nqo),d_tr_ls(:,:,iq-nqo))
2099             CALL histwrite_phy(o_dtr_trsp(iq-nqo),d_tr_trsp(:,:,iq-nqo))
2100             CALL histwrite_phy(o_dtr_sscav(iq-nqo),d_tr_sscav(:,:,iq-nqo))
2101             CALL histwrite_phy(o_dtr_sat(iq-nqo),d_tr_sat(:,:,iq-nqo))
2102             CALL histwrite_phy(o_dtr_uscav(iq-nqo),d_tr_uscav(:,:,iq-nqo))
2103             !--2D fields
2104             CALL histwrite_phy(o_dtr_dry(iq-nqo), flux_tr_dry(:,iq-nqo))
2105             zx_tmp_fi2d=0.
2106             IF (vars_defined) THEN
2107                DO k=1,klev
2108                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,iq-nqo)
2109                ENDDO
2110             ENDIF
2111#ifndef REPROBUS
2112             CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d)
2113#endif
2114            ENDIF
2115          ENDDO
2116       ENDIF
2117
2118       IF (type_trac == 'repr') THEN
2119#ifdef REPROBUS
2120           DO iq=1,nbnas
2121             CALL histwrite_phy(o_nas(iq), nas(:,:,iq))
2122           ENDDO
2123#endif
2124       ENDIF
2125
2126       ENDIF   !(iflag_phytrac==1)
2127
2128
2129       IF (.NOT.vars_defined) THEN
2130          !$OMP MASTER
2131#ifndef CPP_IOIPSL_NO_OUTPUT
2132          DO iff=1,nfiles
2133             IF (clef_files(iff)) THEN
2134                CALL histend(nid_files(iff))
2135                ndex2d = 0
2136                ndex3d = 0
2137             ENDIF ! clef_files
2138          ENDDO !  iff
2139#endif
2140#ifdef CPP_XIOS
2141          !On finalise l'initialisation:
2142          CALL wxios_closedef()
2143#endif
2144          !$OMP END MASTER
2145          !$OMP BARRIER
2146          vars_defined = .TRUE.
2147
2148       ENDIF !--.NOT.vars_defined
2149
2150    ENDDO
2151
2152    IF (vars_defined) THEN
2153       ! On synchronise les fichiers pour IOIPSL
2154#ifndef CPP_IOIPSL_NO_OUTPUT
2155       !$OMP MASTER
2156       DO iff=1,nfiles
2157          IF (ok_sync .AND. clef_files(iff)) THEN
2158             CALL histsync(nid_files(iff))
2159          ENDIF
2160       END DO
2161       !$OMP END MASTER
2162#endif
2163    ENDIF
2164
2165  END SUBROUTINE phys_output_write
2166
2167END MODULE phys_output_write_mod
Note: See TracBrowser for help on using the repository browser.