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

Last change on this file since 1973 was 1971, checked in by idelkadi, 10 years ago

Corrections pour les sorties XIOS :

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