source: LMDZ6/branches/Optimisation_LMDZ/libf/phylmd/phys_output_write_xios_mod.f90 @ 5040

Last change on this file since 5040 was 3769, checked in by adurocher, 4 years ago

Fixed missing xios function in interface

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