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

Last change on this file since 2282 was 2282, checked in by musat, 9 years ago

Correction sorties pression par XIOS dans le cas ok_all_xml

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