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

Last change on this file since 2255 was 2255, checked in by jyg, 9 years ago

Changes to pbl_surface and other routines concerning split/no-split.
+ pbl_surface_mod.F90: call cdrag for (w) region.
+ phyredem.F90: write wake_delta_pbl_TKE.
+ phys_output_write_mod.F90: control output of wake_delta_pbl_TKE by
IF(iflag_pbl_split>=1).
+ lmdz1d.F90: initialize wake_delta_pbl_TKE=0.
+ phys_output_ctrlout_mod.F90: suppression of accents in some variable
attributes.
+ cva_driver.F90: suppression of a print introduced in version 2253.

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