source: LMDZ5/trunk/libf/phylmd/phys_output_mod.F90 @ 1753

Last change on this file since 1753 was 1753, checked in by idelkadi, 11 years ago

Concerns energy conservation.


The source terms of the TKE prognostic equation are diagnosed
from the tendencies (du, dv, dT) associated with subrgrid scale
motions and treated as an additional heat source.
Controled by a new key, iflag_ener_conserv :

0 no conservation

-1 old adhoc correction for kinetic E only (used for CMIP5)

1 conservation
101 conversion from kinetic to heat only
110 conversion from potential to heat only

iflag_ener_conserv=-1 kept as default value for a test period
iflag_ener_conserv=1 is the advisable value
Concerns clesphys.h, and conf_phys.F90
New routine : ener_conserv.F90, called by physic.
New outputs :
bils_ec, contribution to the energy budget of the column of the

additional heat source (in W/m2)

bils_kinetic : change kinetic energy of the column in physics (W/m2)
bils_enthalp : idem for the total column enthalphy
bils_latent : idem for latent heat
Modified files : clesphys.h, conf_phys_m.F90, physiq.F,

phys_output_mod.F90, phys_output_var_mod.F90, phys_output_write.h,
ener_conserv.F90

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 114.9 KB
Line 
1! $Id: phys_output_mod.F90 1753 2013-05-13 12:53:28Z idelkadi $
2!
3! Abderrahmane 12 2007
4!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
5!!! Ecreture des Sorties du modele dans les fichiers Netcdf :
6! histmth.nc : moyennes mensuelles
7! histday.nc : moyennes journalieres
8! histhf.nc  : moyennes toutes les 3 heures
9! histins.nc : valeurs instantanees
10!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
11
12MODULE phys_output_mod
13
14  IMPLICIT NONE
15
16  private histdef2d, histdef3d, conf_physoutputs
17
18
19  integer, parameter                           :: nfiles = 6
20  logical, dimension(nfiles), save             :: clef_files
21  logical, dimension(nfiles), save             :: clef_stations
22  integer, dimension(nfiles), save             :: lev_files
23  integer, dimension(nfiles), save             :: nid_files
24  integer, dimension(nfiles), save  :: nnid_files
25!!$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files)
26  integer, dimension(nfiles), private, save :: nnhorim
27
28  integer, dimension(nfiles), private, save :: nhorim, nvertm
29  integer, dimension(nfiles), private, save :: nvertap, nvertbp, nvertAlt
30  !   integer, dimension(nfiles), private, save :: nvertp0
31  real, dimension(nfiles), private, save                :: zoutm
32  real,                    private, save                :: zdtime
33  CHARACTER(len=20), dimension(nfiles), private, save   :: type_ecri
34  !$OMP THREADPRIVATE(nhorim, nvertm, zoutm,zdtime,type_ecri)
35 ! swaero_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics
36  logical, save                                :: swaero_diag=.FALSE.
37
38
39  !   integer, save                     :: nid_hf3d
40
41!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
42  !! Definition pour chaque variable du niveau d ecriture dans chaque fichier
43!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!/ histmth, histday, histhf, histins /),'!!!!!!!!!!!!
44!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
45
46  integer, private:: levmin(nfiles) = 1
47  integer, private:: levmax(nfiles)
48
49  TYPE ctrl_out
50     integer,dimension(6) :: flag
51     character(len=20)     :: name
52  END TYPE ctrl_out
53
54!!! Comosentes de la coordonnee sigma-hybride
55!!! Ap et Bp
56  type(ctrl_out),save :: o_Ahyb         = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Ap')
57  type(ctrl_out),save :: o_Bhyb         = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Bp')
58  type(ctrl_out),save :: o_Alt          = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Alt')
59
60!!! 1D
61  type(ctrl_out),save :: o_phis         = ctrl_out((/ 1, 1, 10, 5, 1, 1 /), 'phis')
62  type(ctrl_out),save :: o_aire         = ctrl_out((/ 1, 1, 10,  10, 1, 1 /),'aire')
63  type(ctrl_out),save :: o_contfracATM  = ctrl_out((/ 10, 1,  1, 10, 10, 10 /),'contfracATM')
64  type(ctrl_out),save :: o_contfracOR   = ctrl_out((/ 10, 1,  1, 10, 10, 10 /),'contfracOR')
65  type(ctrl_out),save :: o_aireTER      = ctrl_out((/ 10, 10, 1, 10, 10, 10 /),'aireTER')
66
67!!! 2D
68  type(ctrl_out),save :: o_flat         = ctrl_out((/ 5, 1, 10, 10, 5, 10 /),'flat')
69  type(ctrl_out),save :: o_slp          = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'slp')
70  type(ctrl_out),save :: o_tsol         = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'tsol')
71  type(ctrl_out),save :: o_t2m          = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'t2m')
72  type(ctrl_out),save :: o_t2m_min      = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'t2m_min')
73  type(ctrl_out),save :: o_t2m_max      = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'t2m_max')
74  type(ctrl_out),save,dimension(4) :: o_t2m_srf      = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_ter'), &
75       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_lic'), &
76       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_oce'), &
77       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_sic') /)
78
79  type(ctrl_out),save :: o_wind10m      = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'wind10m')
80  type(ctrl_out),save :: o_wind10max    = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'wind10max')
81  type(ctrl_out),save :: o_sicf         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'sicf')
82  type(ctrl_out),save :: o_q2m          = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'q2m')
83  type(ctrl_out),save :: o_ustar        = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'ustar')
84  type(ctrl_out),save :: o_u10m         = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'u10m')
85  type(ctrl_out),save :: o_v10m         = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'v10m')
86  type(ctrl_out),save :: o_psol         = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'psol')
87  type(ctrl_out),save :: o_qsurf        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'qsurf')
88
89  type(ctrl_out),save,dimension(4) :: o_ustar_srf     = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_ter'), &
90       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_lic'), &
91       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_oce'), &
92       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_sic') /)
93  type(ctrl_out),save,dimension(4) :: o_u10m_srf     = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_ter'), &
94       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_lic'), &
95       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_oce'), &
96       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_sic') /)
97
98  type(ctrl_out),save,dimension(4) :: o_v10m_srf     = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_ter'), &
99       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_lic'), &
100       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_oce'), &
101       ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_sic') /)
102
103  type(ctrl_out),save :: o_qsol         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'qsol')
104
105  type(ctrl_out),save :: o_ndayrain     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ndayrain')
106  type(ctrl_out),save :: o_precip       = ctrl_out((/ 1, 1, 1, 10, 5, 10 /),'precip')
107  type(ctrl_out),save :: o_plul         = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'plul')
108
109  type(ctrl_out),save :: o_pluc         = ctrl_out((/ 1, 1, 1, 10, 5, 10 /),'pluc')
110  type(ctrl_out),save :: o_snow         = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'snow')
111  type(ctrl_out),save :: o_evap         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'evap')
112  type(ctrl_out),save,dimension(4) :: o_evap_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_ter'), &
113       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_lic'), &
114       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_oce'), &
115       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_sic') /)
116  type(ctrl_out),save :: o_msnow       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'msnow')
117  type(ctrl_out),save :: o_fsnow       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsnow')
118
119  type(ctrl_out),save :: o_tops         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'tops')
120  type(ctrl_out),save :: o_tops0        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'tops0')
121  type(ctrl_out),save :: o_topl         = ctrl_out((/ 1, 1, 10, 5, 10, 10 /),'topl')
122  type(ctrl_out),save :: o_topl0        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'topl0')
123  type(ctrl_out),save :: o_SWupTOA      = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWupTOA')
124  type(ctrl_out),save :: o_SWupTOAclr   = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWupTOAclr')
125  type(ctrl_out),save :: o_SWdnTOA      = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWdnTOA')
126  type(ctrl_out),save :: o_SWdnTOAclr   = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWdnTOAclr')
127  type(ctrl_out),save :: o_nettop       = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'nettop')
128
129  type(ctrl_out),save :: o_SWup200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'SWup200')
130  type(ctrl_out),save :: o_SWup200clr   = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'SWup200clr')
131  type(ctrl_out),save :: o_SWdn200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'SWdn200')
132  type(ctrl_out),save :: o_SWdn200clr   = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'SWdn200clr')
133
134  ! arajouter
135  !  type(ctrl_out),save :: o_LWupTOA     = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWupTOA')
136  !  type(ctrl_out),save :: o_LWupTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWupTOAclr')
137  !  type(ctrl_out),save :: o_LWdnTOA     = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWdnTOA')
138  !  type(ctrl_out),save :: o_LWdnTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWdnTOAclr')
139
140  type(ctrl_out),save :: o_LWup200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWup200')
141  type(ctrl_out),save :: o_LWup200clr   = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWup200clr')
142  type(ctrl_out),save :: o_LWdn200      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWdn200')
143  type(ctrl_out),save :: o_LWdn200clr   = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWdn200clr')
144  type(ctrl_out),save :: o_sols         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'sols')
145  type(ctrl_out),save :: o_sols0        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'sols0')
146  type(ctrl_out),save :: o_soll         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'soll')
147  type(ctrl_out),save :: o_soll0        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'soll0')
148  type(ctrl_out),save :: o_radsol       = ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'radsol')
149  type(ctrl_out),save :: o_SWupSFC      = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWupSFC')
150  type(ctrl_out),save :: o_SWupSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWupSFCclr')
151  type(ctrl_out),save :: o_SWdnSFC      = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'SWdnSFC')
152  type(ctrl_out),save :: o_SWdnSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWdnSFCclr')
153  type(ctrl_out),save :: o_LWupSFC      = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWupSFC')
154  type(ctrl_out),save :: o_LWupSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWupSFCclr')
155  type(ctrl_out),save :: o_LWdnSFC      = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWdnSFC')
156  type(ctrl_out),save :: o_LWdnSFCclr   = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWdnSFCclr')
157  type(ctrl_out),save :: o_bils         = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils')
158  type(ctrl_out),save :: o_bils_ec         = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_ec')
159  type(ctrl_out),save :: o_bils_kinetic         = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_kinetic')
160  type(ctrl_out),save :: o_bils_enthalp         = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_enthalp')
161  type(ctrl_out),save :: o_bils_latent         = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_latent')
162  type(ctrl_out),save :: o_sens         = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'sens')
163  type(ctrl_out),save :: o_fder         = ctrl_out((/ 1, 2, 10, 10, 10, 10 /),'fder')
164  type(ctrl_out),save :: o_ffonte       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ffonte')
165  type(ctrl_out),save :: o_fqcalving    = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fqcalving')
166  type(ctrl_out),save :: o_fqfonte      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fqfonte')
167
168  type(ctrl_out),save :: o_taux         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'taux')
169  type(ctrl_out),save :: o_tauy         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'tauy')
170  type(ctrl_out),save,dimension(4) :: o_taux_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_ter'), &
171       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_lic'), &
172       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_oce'), &
173       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_sic') /)
174
175  type(ctrl_out),save,dimension(4) :: o_tauy_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_ter'), &
176       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_lic'), &
177       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_oce'), &
178       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_sic') /)
179
180
181  type(ctrl_out),save,dimension(4) :: o_pourc_srf    = (/ ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_ter'), &
182       ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_lic'), &
183       ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_oce'), &
184       ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_sic') /)     
185
186  type(ctrl_out),save,dimension(4) :: o_fract_srf    = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_ter'), &
187       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_lic'), &
188       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_oce'), &
189       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_sic') /)
190
191  type(ctrl_out),save,dimension(4) :: o_tsol_srf     = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_ter'), &
192       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_lic'), &
193       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_oce'), &
194       ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_sic') /)
195
196  type(ctrl_out),save,dimension(4) :: o_evappot_srf  = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evappot_ter'), &
197       ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'evappot_lic'), &
198       ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'evappot_oce'), &
199       ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'evappot_sic') /)
200
201  type(ctrl_out),save,dimension(4) :: o_sens_srf     = (/ ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_ter'), &
202       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_lic'), &
203       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_oce'), &
204       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_sic') /)
205
206  type(ctrl_out),save,dimension(4) :: o_lat_srf      = (/ ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_ter'), &
207       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_lic'), &
208       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_oce'), &
209       ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_sic') /)
210
211  type(ctrl_out),save,dimension(4) :: o_flw_srf      = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_ter'), &
212       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_lic'), &
213       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_oce'), &
214       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_sic') /)
215
216  type(ctrl_out),save,dimension(4) :: o_fsw_srf      = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_ter'), &
217       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_lic'), &
218       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_oce'), &
219       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_sic') /)
220
221  type(ctrl_out),save,dimension(4) :: o_wbils_srf    = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_ter'), &
222       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_lic'), &
223       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_oce'), &
224       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_sic') /)
225
226  type(ctrl_out),save,dimension(4) :: o_wbilo_srf    = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_ter'), &
227       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_lic'), &
228       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_oce'), &
229       ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_sic') /)
230
231
232  type(ctrl_out),save :: o_cdrm         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'cdrm')
233  type(ctrl_out),save :: o_cdrh         = ctrl_out((/ 1, 10, 10, 7, 10, 10 /),'cdrh')
234  type(ctrl_out),save :: o_cldl         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldl')
235  type(ctrl_out),save :: o_cldm         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldm')
236  type(ctrl_out),save :: o_cldh         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldh')
237  type(ctrl_out),save :: o_cldt         = ctrl_out((/ 1, 1, 2, 10, 5, 10 /),'cldt')
238  type(ctrl_out),save :: o_cldq         = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldq')
239  type(ctrl_out),save :: o_lwp          = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'lwp')
240  type(ctrl_out),save :: o_iwp          = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'iwp')
241  type(ctrl_out),save :: o_ue           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ue')
242  type(ctrl_out),save :: o_ve           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ve')
243  type(ctrl_out),save :: o_uq           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'uq')
244  type(ctrl_out),save :: o_vq           = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'vq')
245
246  type(ctrl_out),save :: o_cape         = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'cape')
247  type(ctrl_out),save :: o_pbase        = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'pbase')
248  type(ctrl_out),save :: o_ptop         = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'ptop')
249  type(ctrl_out),save :: o_fbase        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fbase')
250  type(ctrl_out),save :: o_plcl        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'plcl')
251  type(ctrl_out),save :: o_plfc        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'plfc')
252  type(ctrl_out),save :: o_wbeff        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbeff')
253  type(ctrl_out),save :: o_prw          = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'prw')
254
255  type(ctrl_out),save :: o_s_pblh       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_pblh')
256  type(ctrl_out),save :: o_s_pblt       = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_pblt')
257  type(ctrl_out),save :: o_s_lcl        = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_lcl')
258  type(ctrl_out),save :: o_s_therm      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_therm')
259  !IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
260  ! type(ctrl_out),save :: o_s_capCL      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_capCL')
261  ! type(ctrl_out),save :: o_s_oliqCL     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_oliqCL')
262  ! type(ctrl_out),save :: o_s_cteiCL     = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_cteiCL')
263  ! type(ctrl_out),save :: o_s_trmb1      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb1')
264  ! type(ctrl_out),save :: o_s_trmb2      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb2')
265  ! type(ctrl_out),save :: o_s_trmb3      = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb3')
266
267  type(ctrl_out),save :: o_slab_bils    = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'slab_bils_oce')
268
269  type(ctrl_out),save :: o_ale_bl       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale_bl')
270  type(ctrl_out),save :: o_alp_bl       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl')
271  type(ctrl_out),save :: o_ale_wk       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale_wk')
272  type(ctrl_out),save :: o_alp_wk       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_wk')
273
274  type(ctrl_out),save :: o_ale          = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale')
275  type(ctrl_out),save :: o_alp          = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp')
276  type(ctrl_out),save :: o_cin          = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'cin')
277  type(ctrl_out),save :: o_wape         = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'wape')
278
279!!! nrlmd le 10/04/2012
280
281!-------Spectre de thermiques de type 2 au LCL
282  type(ctrl_out),save :: o_n2                = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'n2')
283  type(ctrl_out),save :: o_s2                = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'s2')
284                                                                             
285!-------Déclenchement stochastique                                           
286  type(ctrl_out),save :: o_proba_notrig      = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'proba_notrig')
287  type(ctrl_out),save :: o_random_notrig     = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'random_notrig')
288  type(ctrl_out),save :: o_ale_bl_stat       = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'ale_bl_stat')
289  type(ctrl_out),save :: o_ale_bl_trig       = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'ale_bl_trig')
290
291!-------Fermeture statistique
292  type(ctrl_out),save :: o_alp_bl_det        = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_det')
293  type(ctrl_out),save :: o_alp_bl_fluct_m    = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_fluct_m')
294  type(ctrl_out),save :: o_alp_bl_fluct_tke  = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_fluct_tke')
295  type(ctrl_out),save :: o_alp_bl_conv       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_conv')
296  type(ctrl_out),save :: o_alp_bl_stat       = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_stat')
297
298!!! fin nrlmd le 10/04/2012
299
300  ! Champs interpolles sur des niveaux de pression ??? a faire correctement
301
302  type(ctrl_out),save,dimension(7) :: o_uSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u850'), &
303       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u700'), &
304       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u500'), &
305       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u200'), &
306       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u100'), &
307       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u50'), &
308       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u10') /)
309
310
311  type(ctrl_out),save,dimension(7) :: o_vSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v850'), &
312       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v700'), &
313       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v500'), &
314       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v200'), &
315       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v100'), &
316       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v50'), &
317       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v10') /)
318
319  type(ctrl_out),save,dimension(7) :: o_wSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w850'), &
320       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w700'), &
321       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w500'), &
322       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w200'), &
323       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w100'), &
324       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w50'), &
325       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w10') /)
326
327  type(ctrl_out),save,dimension(7) :: o_tSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t850'), &
328       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t700'), &
329       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t500'), &
330       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t200'), &
331       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t100'), &
332       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t50'), &
333       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t10') /)
334
335  type(ctrl_out),save,dimension(7) :: o_qSTDlevs     = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q850'), &
336       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q700'), &
337       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q500'), &
338       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q200'), &
339       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q100'), &
340       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q50'), &
341       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q10') /)
342
343  type(ctrl_out),save,dimension(7) :: o_zSTDlevs   = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z850'), &
344       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z700'), &
345       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z500'), &
346       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z200'), &
347       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z100'), &
348       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z50'), &
349       ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z10') /)
350
351
352  type(ctrl_out),save :: o_t_oce_sic    = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'t_oce_sic')
353
354  type(ctrl_out),save :: o_weakinv      = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'weakinv')
355  type(ctrl_out),save :: o_dthmin       = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'dthmin')
356  type(ctrl_out),save,dimension(4) :: o_u10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_ter'), &
357       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_lic'), &
358       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_oce'), &
359       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_sic') /)
360
361  type(ctrl_out),save,dimension(4) :: o_v10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_ter'), &
362       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_lic'), &
363       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_oce'), &
364       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_sic') /)
365
366  type(ctrl_out),save :: o_cldtau       = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'cldtau')                     
367  type(ctrl_out),save :: o_cldemi       = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'cldemi')
368  type(ctrl_out),save :: o_rh2m         = ctrl_out((/ 5, 5, 10, 10, 10, 10 /),'rh2m')
369  type(ctrl_out),save :: o_rh2m_min     = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'rh2m_min')
370  type(ctrl_out),save :: o_rh2m_max     = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'rh2m_max')
371  type(ctrl_out),save :: o_qsat2m       = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'qsat2m')
372  type(ctrl_out),save :: o_tpot         = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'tpot')
373  type(ctrl_out),save :: o_tpote        = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'tpote')
374  type(ctrl_out),save :: o_tke          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tke ')
375  type(ctrl_out),save :: o_tke_max      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tke_max')
376
377  type(ctrl_out),save,dimension(4) :: o_tke_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_ter'), &
378       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_lic'), &
379       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_oce'), &
380       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_sic') /)
381
382  type(ctrl_out),save,dimension(4) :: o_tke_max_srf  = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_ter'), &
383       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_lic'), &
384       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_oce'), &
385       ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_sic') /)
386
387  type(ctrl_out),save :: o_kz           = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'kz')
388  type(ctrl_out),save :: o_kz_max       = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'kz_max')
389  type(ctrl_out),save :: o_SWnetOR      = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'SWnetOR')
390  type(ctrl_out),save :: o_SWdownOR     = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'SWdownOR')
391  type(ctrl_out),save :: o_LWdownOR     = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'LWdownOR')
392
393  type(ctrl_out),save :: o_snowl        = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'snowl')
394  type(ctrl_out),save :: o_cape_max     = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'cape_max')
395  type(ctrl_out),save :: o_solldown     = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'solldown')
396
397  type(ctrl_out),save :: o_dtsvdfo      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfo')
398  type(ctrl_out),save :: o_dtsvdft      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdft')
399  type(ctrl_out),save :: o_dtsvdfg      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfg')
400  type(ctrl_out),save :: o_dtsvdfi      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfi')
401  type(ctrl_out),save :: o_rugs         = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'rugs')
402
403  type(ctrl_out),save :: o_topswad      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'topswad')
404  type(ctrl_out),save :: o_topswad0     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'topswad0')
405  type(ctrl_out),save :: o_topswai      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'topswai')
406  type(ctrl_out),save :: o_solswad      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswad')
407  type(ctrl_out),save :: o_solswad0     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswad0')
408  type(ctrl_out),save :: o_solswai      = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswai')
409
410  type(ctrl_out),save,dimension(10) :: o_tausumaero  = (/ ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASBCM'), &
411       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASPOMM'), &
412       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSO4M'), &
413       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSO4M'), &
414       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_SSSSM'), &
415       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSSM'), &
416       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSSM'), &
417       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CIDUSTM'), &
418       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIBCM'), &
419       ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIPOMM') /)
420
421  type(ctrl_out),save :: o_od550aer     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od550aer')
422  type(ctrl_out),save :: o_od865aer     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od865aer')
423  type(ctrl_out),save :: o_absvisaer    = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'absvisaer')
424  type(ctrl_out),save :: o_od550lt1aer  = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od550lt1aer')
425
426  type(ctrl_out),save :: o_sconcso4     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcso4')
427  type(ctrl_out),save :: o_sconcoa      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcoa')
428  type(ctrl_out),save :: o_sconcbc      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcbc')
429  type(ctrl_out),save :: o_sconcss      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcss')
430  type(ctrl_out),save :: o_sconcdust    = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcdust')
431  type(ctrl_out),save :: o_concso4      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concso4')
432  type(ctrl_out),save :: o_concoa       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concoa')
433  type(ctrl_out),save :: o_concbc       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concbc')
434  type(ctrl_out),save :: o_concss       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concss')
435  type(ctrl_out),save :: o_concdust     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concdust')
436  type(ctrl_out),save :: o_loadso4      = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadso4')
437  type(ctrl_out),save :: o_loadoa       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadoa')
438  type(ctrl_out),save :: o_loadbc       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadbc')
439  type(ctrl_out),save :: o_loadss       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadss')
440  type(ctrl_out),save :: o_loaddust     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loaddust')
441
442  type(ctrl_out),save :: o_swtoaas_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoaas_nat')
443  type(ctrl_out),save :: o_swsrfas_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfas_nat')
444  type(ctrl_out),save :: o_swtoacs_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacs_nat')
445  type(ctrl_out),save :: o_swsrfcs_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcs_nat')
446
447  type(ctrl_out),save :: o_swtoaas_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoaas_ant')
448  type(ctrl_out),save :: o_swsrfas_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfas_ant')
449  type(ctrl_out),save :: o_swtoacs_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacs_ant')
450  type(ctrl_out),save :: o_swsrfcs_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcs_ant')
451
452  type(ctrl_out),save :: o_swtoacf_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_nat')
453  type(ctrl_out),save :: o_swsrfcf_nat  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_nat')
454  type(ctrl_out),save :: o_swtoacf_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_ant')
455  type(ctrl_out),save :: o_swsrfcf_ant  = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_ant')
456  type(ctrl_out),save :: o_swtoacf_zero = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_zero')
457  type(ctrl_out),save :: o_swsrfcf_zero = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_zero')
458
459  type(ctrl_out),save :: o_cldncl       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'cldncl')
460  type(ctrl_out),save :: o_reffclwtop   = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'reffclwtop')
461  type(ctrl_out),save :: o_cldnvi       = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'cldnvi')
462  type(ctrl_out),save :: o_lcc          = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'lcc')
463
464
465!!!!!!!!!!!!!!!!!!!!!! 3D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
466  type(ctrl_out),save :: o_ec550aer     = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'ec550aer')
467  type(ctrl_out),save :: o_lwcon        = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'lwcon')
468  type(ctrl_out),save :: o_iwcon        = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'iwcon')
469  type(ctrl_out),save :: o_temp         = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'temp')
470  type(ctrl_out),save :: o_theta        = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'theta')
471  type(ctrl_out),save :: o_ovap         = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'ovap')
472  type(ctrl_out),save :: o_ovapinit     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ovapinit')
473  type(ctrl_out),save :: o_oliq         = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'oliq')
474  type(ctrl_out),save :: o_wvapp        = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'wvapp')
475  type(ctrl_out),save :: o_geop         = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'geop')
476  type(ctrl_out),save :: o_vitu         = ctrl_out((/ 2, 3, 4, 6, 10, 10 /),'vitu')
477  type(ctrl_out),save :: o_vitv         = ctrl_out((/ 2, 3, 4, 6, 10, 10 /),'vitv')
478  type(ctrl_out),save :: o_vitw         = ctrl_out((/ 2, 3, 10, 6, 10, 10 /),'vitw')
479  type(ctrl_out),save :: o_pres         = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'pres')
480  type(ctrl_out),save :: o_paprs        = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'paprs')
481  type(ctrl_out),save :: o_mass        = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'mass')
482  type(ctrl_out),save :: o_zfull       = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'zfull')
483  type(ctrl_out),save :: o_zhalf       = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'zhalf')
484  type(ctrl_out),save :: o_rneb         = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rneb')
485  type(ctrl_out),save :: o_rnebcon      = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rnebcon')
486  type(ctrl_out),save :: o_rnebls       = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rnebls')
487  type(ctrl_out),save :: o_rhum         = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rhum')
488  type(ctrl_out),save :: o_ozone        = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ozone')
489  type(ctrl_out),save :: o_ozone_light  = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ozone_daylight')
490  type(ctrl_out),save :: o_upwd         = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'upwd')
491  type(ctrl_out),save :: o_dtphy        = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'dtphy')
492  type(ctrl_out),save :: o_dqphy        = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'dqphy')
493  type(ctrl_out),save :: o_pr_con_l     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_con_l')
494  type(ctrl_out),save :: o_pr_con_i     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_con_i')
495  type(ctrl_out),save :: o_pr_lsc_l     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_lsc_l')
496  type(ctrl_out),save :: o_pr_lsc_i     = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_lsc_i')
497  type(ctrl_out),save :: o_re           = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'re')
498  type(ctrl_out),save :: o_fl           = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'fl')
499  type(ctrl_out),save :: o_scdnc        = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'scdnc')
500  type(ctrl_out),save :: o_reffclws     = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'reffclws')
501  type(ctrl_out),save :: o_reffclwc     = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'reffclwc')
502  type(ctrl_out),save :: o_lcc3d        = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'lcc3d')
503  type(ctrl_out),save :: o_lcc3dcon     = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'lcc3dcon')
504  type(ctrl_out),save :: o_lcc3dstra    = ctrl_out((/ 2,  6, 10, 10, 10, 10 /),'lcc3dstra')
505!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
506
507  type(ctrl_out),save,dimension(4) :: o_albe_srf     = (/ ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_ter'), &
508       ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_lic'), &
509       ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_oce'), &
510       ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_sic') /)
511
512  type(ctrl_out),save,dimension(4) :: o_ages_srf     = (/ ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_ter'), &
513       ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_lic'), &
514       ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_oce'), &
515       ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_sic') /)
516
517  type(ctrl_out),save,dimension(4) :: o_rugs_srf     = (/ ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_ter'), &
518       ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_lic'), &
519       ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_oce'), &
520       ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_sic') /)
521
522  type(ctrl_out),save :: o_alb1         = ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'alb1')
523  type(ctrl_out),save :: o_alb2       = ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'alb2')
524
525  type(ctrl_out),save :: o_clwcon       = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'clwcon')
526  type(ctrl_out),save :: o_Ma           = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'Ma')
527  type(ctrl_out),save :: o_dnwd         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dnwd')
528  type(ctrl_out),save :: o_dnwd0        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dnwd0')
529  type(ctrl_out),save :: o_mc           = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'mc')
530  type(ctrl_out),save :: o_ftime_con    = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ftime_con')
531  type(ctrl_out),save :: o_dtdyn        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtdyn')
532  type(ctrl_out),save :: o_dqdyn        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqdyn')
533  type(ctrl_out),save :: o_dudyn        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dudyn')  !AXC
534  type(ctrl_out),save :: o_dvdyn        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvdyn')  !AXC
535  type(ctrl_out),save :: o_dtcon        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtcon')
536  type(ctrl_out),save :: o_ducon        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ducon')
537  type(ctrl_out),save :: o_dvcon        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvcon')
538  type(ctrl_out),save :: o_dqcon        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqcon')
539  type(ctrl_out),save :: o_dtwak        = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'dtwak')
540  type(ctrl_out),save :: o_dqwak        = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'dqwak')
541  type(ctrl_out),save :: o_wake_h       = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_h')
542  type(ctrl_out),save :: o_wake_s       = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_s')
543  type(ctrl_out),save :: o_wake_deltat  = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_deltat')
544  type(ctrl_out),save :: o_wake_deltaq  = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_deltaq')
545  type(ctrl_out),save :: o_wake_omg     = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_omg')
546  type(ctrl_out),save :: o_wdtrainA     = ctrl_out((/ 4, 1, 10,  4,  1, 10 /),'wdtrainA') !<<RomP
547  type(ctrl_out),save :: o_wdtrainM     = ctrl_out((/ 4, 1, 10,  4,  1, 10 /),'wdtrainM') !<<RomP
548  type(ctrl_out),save :: o_Vprecip      = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'Vprecip')
549  type(ctrl_out),save :: o_ftd          = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'ftd')
550  type(ctrl_out),save :: o_fqd          = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'fqd')
551  type(ctrl_out),save :: o_dtlsc        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlsc')
552  type(ctrl_out),save :: o_dtlschr      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlschr')
553  type(ctrl_out),save :: o_dqlsc        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqlsc')
554  type(ctrl_out),save :: o_beta_prec    = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'beta_prec')
555  type(ctrl_out),save :: o_dtvdf        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtvdf')
556  type(ctrl_out),save :: o_dqvdf        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqvdf')
557  type(ctrl_out),save :: o_dteva        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dteva')
558  type(ctrl_out),save :: o_dqeva        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqeva')
559
560!!!!!!!!!!!!!!!! Specifique thermiques
561  type(ctrl_out),save :: o_dqlscth        = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dqlscth')
562  type(ctrl_out),save :: o_dqlscst        = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dqlscst')
563  type(ctrl_out),save :: o_dtlscth        = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtlscth')
564  type(ctrl_out),save :: o_dtlscst        = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtlscst')
565  type(ctrl_out),save :: o_plulth        = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'plulth')
566  type(ctrl_out),save :: o_plulst        = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'plulst')
567  type(ctrl_out),save :: o_lmaxth        = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'lmaxth')
568  type(ctrl_out),save :: o_ptconvth        = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ptconvth')
569!!!!!!!!!!!!!!!!!!!!!!!!
570
571
572  type(ctrl_out),save :: o_ptconv       = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ptconv')
573  type(ctrl_out),save :: o_ratqs        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ratqs')
574  type(ctrl_out),save :: o_dtthe        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtthe')
575  type(ctrl_out),save :: o_f_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'f_th')
576  type(ctrl_out),save :: o_e_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'e_th')
577  type(ctrl_out),save :: o_w_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'w_th')
578  type(ctrl_out),save :: o_ftime_th     = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ftime_th')
579  type(ctrl_out),save :: o_q_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'q_th')
580  type(ctrl_out),save :: o_a_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'a_th')
581  type(ctrl_out),save :: o_d_th         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'d_th')
582  type(ctrl_out),save :: o_f0_th        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'f0_th')
583  type(ctrl_out),save :: o_zmax_th      = ctrl_out((/ 4,  4,  4,  5, 10, 10 /),'zmax_th')
584  type(ctrl_out),save :: o_dqthe        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqthe')
585  type(ctrl_out),save :: o_dtajs        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtajs')
586  type(ctrl_out),save :: o_dqajs        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqajs')
587  type(ctrl_out),save :: o_dtswr        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtswr')
588  type(ctrl_out),save :: o_dtsw0        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtsw0')
589  type(ctrl_out),save :: o_dtlwr        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlwr')
590  type(ctrl_out),save :: o_dtlw0        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlw0')
591  type(ctrl_out),save :: o_dtec         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtec')
592  type(ctrl_out),save :: o_duvdf        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duvdf')
593  type(ctrl_out),save :: o_dvvdf        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvvdf')
594  type(ctrl_out),save :: o_duoro        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duoro')
595  type(ctrl_out),save :: o_dvoro        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvoro')
596  type(ctrl_out),save :: o_dulif        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dulif')
597  type(ctrl_out),save :: o_dvlif        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvlif')
598  type(ctrl_out),save :: o_duhin        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duhin')
599  type(ctrl_out),save :: o_dvhin        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvhin')
600  type(ctrl_out),save :: o_dtoro        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtoro')
601  type(ctrl_out),save :: o_dtlif        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlif')
602  type(ctrl_out),save :: o_dthin        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dthin')
603
604  type(ctrl_out),save,allocatable :: o_trac(:)
605  type(ctrl_out),save,allocatable :: o_trac_cum(:)
606
607  type(ctrl_out),save :: o_rsu        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsu')
608  type(ctrl_out),save :: o_rsd        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsd')
609  type(ctrl_out),save :: o_rlu        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rlu')
610  type(ctrl_out),save :: o_rld        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rld')
611  type(ctrl_out),save :: o_rsucs      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsucs')
612  type(ctrl_out),save :: o_rsdcs      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsdcs')
613  type(ctrl_out),save :: o_rlucs      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rlucs')
614  type(ctrl_out),save :: o_rldcs      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rldcs')
615
616  type(ctrl_out),save :: o_tnt          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnt')
617  type(ctrl_out),save :: o_tntc         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntc')
618  type(ctrl_out),save :: o_tntr        = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntr')
619  type(ctrl_out),save :: o_tntscpbl          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntscpbl')
620
621  type(ctrl_out),save :: o_tnhus          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhus')
622  type(ctrl_out),save :: o_tnhusc         = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhusc')
623  type(ctrl_out),save :: o_tnhusscpbl     = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhusscpbl')
624
625  type(ctrl_out),save :: o_evu          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'evu')
626
627  type(ctrl_out),save :: o_h2o          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'h2o')
628
629  type(ctrl_out),save :: o_mcd          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'mcd')
630  type(ctrl_out),save :: o_dmc          = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dmc')
631  type(ctrl_out),save :: o_ref_liq      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ref_liq')
632  type(ctrl_out),save :: o_ref_ice      = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ref_ice')
633
634  type(ctrl_out),save :: o_rsut4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsut4co2')
635  type(ctrl_out),save :: o_rlut4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlut4co2')
636  type(ctrl_out),save :: o_rsutcs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsutcs4co2')
637  type(ctrl_out),save :: o_rlutcs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlutcs4co2')
638
639  type(ctrl_out),save :: o_rsu4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsu4co2')
640  type(ctrl_out),save :: o_rlu4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlu4co2')
641  type(ctrl_out),save :: o_rsucs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsucs4co2')
642  type(ctrl_out),save :: o_rlucs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlucs4co2')
643  type(ctrl_out),save :: o_rsd4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsd4co2')
644  type(ctrl_out),save :: o_rld4co2     = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rld4co2')
645  type(ctrl_out),save :: o_rsdcs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsdcs4co2')
646  type(ctrl_out),save :: o_rldcs4co2   = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rldcs4co2')
647
648
649CONTAINS
650
651!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
652!!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!!
653  !! histbeg, histvert et histdef
654!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
655
656  SUBROUTINE phys_output_open(rlon,rlat,pim,tabij,ipt,jpt,plon,plat, &
657       jjmp1,nlevSTD,clevSTD,nbteta, &
658       ctetaSTD, dtime, ok_veget, &
659       type_ocean, iflag_pbl,ok_mensuel,ok_journe, &
660       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
661       phys_out_filestations, &
662       new_aod, aerosol_couple)   
663
664    USE iophy
665    USE dimphy
666    USE infotrac
667    USE ioipsl
668    USE phys_cal_mod, only : hour
669    USE mod_phys_lmdz_para
670    USE aero_mod, only : naero_spc,name_aero
671
672    IMPLICIT NONE
673    include "dimensions.h"
674    include "temps.h"
675    include "indicesol.h"
676    include "clesphys.h"
677    include "thermcell.h"
678    include "comvert.h"
679    include "iniprint.h"
680
681    real,dimension(klon),intent(in) :: rlon
682    real,dimension(klon),intent(in) :: rlat
683    integer, intent(in)             :: pim
684    INTEGER, DIMENSION(pim)            :: tabij
685    INTEGER,dimension(pim), intent(in) :: ipt, jpt
686    REAL,dimension(pim), intent(in) :: plat, plon
687    REAL,dimension(pim,2) :: plat_bounds, plon_bounds
688
689    integer                               :: jjmp1
690    integer                               :: nbteta, nlevSTD, radpas
691    logical                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
692    logical                               :: ok_LES,ok_ade,ok_aie
693    logical                               :: new_aod, aerosol_couple
694    integer, intent(in)::  read_climoz ! read ozone climatology
695    !     Allowed values are 0, 1 and 2
696    !     0: do not read an ozone climatology
697    !     1: read a single ozone climatology that will be used day and night
698    !     2: read two ozone climatologies, the average day and night
699    !     climatology and the daylight climatology
700
701    real                                  :: dtime
702    integer                               :: idayref
703    real                                  :: zjulian
704    real, dimension(klev)                 :: Ahyb, Bhyb, Alt
705    character(len=4), dimension(nlevSTD)  :: clevSTD
706    integer                               :: nsrf, k, iq, iiq, iff, i, j, ilev
707    integer                               :: naero
708    logical                               :: ok_veget
709    integer                               :: iflag_pbl
710    CHARACTER(len=4)                      :: bb2
711    CHARACTER(len=2)                      :: bb3
712    character(len=6)                      :: type_ocean
713    CHARACTER(len=3)                      :: ctetaSTD(nbteta)
714    real, dimension(nfiles)               :: ecrit_files
715    CHARACTER(len=20), dimension(nfiles)  :: phys_out_filenames
716    INTEGER, dimension(iim*jjmp1)         ::  ndex2d
717    INTEGER, dimension(iim*jjmp1*klev)    :: ndex3d
718    integer                               :: imin_ins, imax_ins
719    integer                               :: jmin_ins, jmax_ins
720    integer, dimension(nfiles)            :: phys_out_levmin, phys_out_levmax
721    integer, dimension(nfiles)            :: phys_out_filelevels
722    CHARACTER(len=20), dimension(nfiles)  :: type_ecri_files, phys_out_filetypes
723    character(len=20), dimension(nfiles)  :: chtimestep   = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq', 'DefFreq' /)
724    logical, dimension(nfiles)            :: phys_out_filekeys
725    logical, dimension(nfiles)            :: phys_out_filestations
726
727!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
728    !                 entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
729
730    logical, dimension(nfiles), save  :: phys_out_regfkey       = (/ .false., .false., .false.,  .false., .false., .false. /)
731    real, dimension(nfiles), save     :: phys_out_lonmin        = (/   -180.,   -180.,   -180.,    -180.,   -180.,   -180. /)
732    real, dimension(nfiles), save     :: phys_out_lonmax        = (/    180.,    180.,    180.,     180.,    180.,    180. /)
733    real, dimension(nfiles), save     :: phys_out_latmin        = (/    -90.,    -90.,    -90.,     -90.,    -90.,    -90. /)
734    real, dimension(nfiles), save     :: phys_out_latmax        = (/     90.,     90.,     90.,     90.,     90.,     90. /)
735
736    write(lunout,*) 'Debut phys_output_mod.F90'
737    ! Initialisations (Valeurs par defaut
738
739    if (.not. allocated(o_trac)) ALLOCATE(o_trac(nqtot))
740    if (.not. allocated(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot))
741
742    levmax = (/ klev, klev, klev, klev, klev, klev /)
743
744    phys_out_filenames(1) = 'histmth'
745    phys_out_filenames(2) = 'histday'
746    phys_out_filenames(3) = 'histhf'
747    phys_out_filenames(4) = 'histins'
748    phys_out_filenames(5) = 'histLES'
749    phys_out_filenames(6) = 'histstn'
750
751    type_ecri(1) = 'ave(X)'
752    type_ecri(2) = 'ave(X)'
753    type_ecri(3) = 'ave(X)'
754    type_ecri(4) = 'inst(X)'
755    type_ecri(5) = 'ave(X)'
756    type_ecri(6) = 'inst(X)'
757
758    clef_files(1) = ok_mensuel
759    clef_files(2) = ok_journe
760    clef_files(3) = ok_hf
761    clef_files(4) = ok_instan
762    clef_files(5) = ok_LES
763    clef_files(6) = ok_instan
764
765    !sortir des fichiers "stations" si clef_stations(:)=.TRUE.
766    clef_stations(1) = .FALSE.
767    clef_stations(2) = .FALSE.
768    clef_stations(3) = .FALSE.
769    clef_stations(4) = .FALSE.
770    clef_stations(5) = .FALSE.
771    clef_stations(6) = .FALSE.
772
773    lev_files(1) = lev_histmth
774    lev_files(2) = lev_histday
775    lev_files(3) = lev_histhf
776    lev_files(4) = lev_histins
777    lev_files(5) = lev_histLES
778    lev_files(6) = lev_histins
779
780    ecrit_files(1) = ecrit_mth
781    ecrit_files(2) = ecrit_day
782    ecrit_files(3) = ecrit_hf
783    ecrit_files(4) = ecrit_ins
784    ecrit_files(5) = ecrit_LES
785    ecrit_files(6) = ecrit_ins
786
787    !! Lectures des parametres de sorties dans physiq.def
788
789    call getin('phys_out_regfkey',phys_out_regfkey)
790    call getin('phys_out_lonmin',phys_out_lonmin)
791    call getin('phys_out_lonmax',phys_out_lonmax)
792    call getin('phys_out_latmin',phys_out_latmin)
793    call getin('phys_out_latmax',phys_out_latmax)
794    phys_out_levmin(:)=levmin(:)
795    call getin('phys_out_levmin',levmin)
796    phys_out_levmax(:)=levmax(:)
797    call getin('phys_out_levmax',levmax)
798    call getin('phys_out_filenames',phys_out_filenames)
799    phys_out_filekeys(:)=clef_files(:)
800    call getin('phys_out_filekeys',clef_files)
801    phys_out_filestations(:)=clef_stations(:)
802    call getin('phys_out_filestations',clef_stations)
803    phys_out_filelevels(:)=lev_files(:)
804    call getin('phys_out_filelevels',lev_files)
805    call getin('phys_out_filetimesteps',chtimestep)
806    phys_out_filetypes(:)=type_ecri(:)
807    call getin('phys_out_filetypes',type_ecri)
808
809    type_ecri_files(:)=type_ecri(:)
810
811    write(lunout,*)'phys_out_lonmin=',phys_out_lonmin
812    write(lunout,*)'phys_out_lonmax=',phys_out_lonmax
813    write(lunout,*)'phys_out_latmin=',phys_out_latmin
814    write(lunout,*)'phys_out_latmax=',phys_out_latmax
815    write(lunout,*)'phys_out_filenames=',phys_out_filenames
816    write(lunout,*)'phys_out_filetypes=',type_ecri
817    write(lunout,*)'phys_out_filekeys=',clef_files
818    write(lunout,*)'phys_out_filestations=',clef_stations
819    write(lunout,*)'phys_out_filelevels=',lev_files
820
821!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
822    ! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
823    ! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
824!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
825
826    zdtime = dtime         ! Frequence ou l on moyenne
827
828    ! Calcul des Ahyb, Bhyb et Alt
829    do k=1,klev
830       Ahyb(k)=(ap(k)+ap(k+1))/2.
831       Bhyb(k)=(bp(k)+bp(k+1))/2.
832       Alt(k)=log(preff/presnivs(k))*8.
833    enddo
834    !          if(prt_level.ge.1) then
835    write(lunout,*)'Ap Hybrid = ',Ahyb(1:klev)
836    write(lunout,*)'Bp Hybrid = ',Bhyb(1:klev)
837    write(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)
838    !          endif
839    DO iff=1,nfiles
840
841       ! Calculate ecrit_files for all files
842       if ( chtimestep(iff).eq.'DefFreq' ) then
843          ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf ...)*86400.
844          ecrit_files(iff)=ecrit_files(iff)*86400.
845       else
846          call convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))
847       endif
848       write(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff)
849
850       zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
851
852       IF (clef_files(iff)) THEN
853
854          idayref = day_ref
855!          CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)       
856! correction pour l heure initiale                               !jyg
857!                                                                !jyg
858          CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian)         !jyg
859! correction pour l heure initiale                               !jyg
860!                                                                !jyg
861!!!      CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)       !jyg
862! correction pour l heure initiale                               !jyg
863!                                                                !jyg
864!      CALL ymds2ju(annee_ref, 1, idayref, hour, zjulian)         !jyg
865
866!!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
867!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
868          if (phys_out_regfkey(iff)) then
869
870             imin_ins=1
871             imax_ins=iim
872             jmin_ins=1
873             jmax_ins=jjmp1
874
875             ! correction abderr       
876             do i=1,iim
877                write(lunout,*)'io_lon(i)=',io_lon(i)
878                if (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
879                if (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
880             enddo
881
882             do j=1,jjmp1
883                write(lunout,*)'io_lat(j)=',io_lat(j)
884                if (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
885                if (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
886             enddo
887
888             write(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', &
889                  imin_ins,imax_ins,jmin_ins,jmax_ins
890             write(lunout,*)'longitudes : ', &
891                  io_lon(imin_ins),io_lon(imax_ins), &
892                  'latitudes : ', &
893                  io_lat(jmax_ins),io_lat(jmin_ins)
894
895             CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, &
896                  imin_ins,imax_ins-imin_ins+1, &
897                  jmin_ins,jmax_ins-jmin_ins+1, &
898                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
899!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
900             !IM fichiers stations
901          else if (clef_stations(iff)) THEN
902
903             write(lunout,*)'phys_output_mod phys_out_filenames=',phys_out_filenames(iff)
904
905             call histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &
906                  phys_out_filenames(iff), &
907                  itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
908          else
909             CALL histbeg_phy(phys_out_filenames(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
910          endif
911
912          CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "Pa", &
913               levmax(iff) - levmin(iff) + 1, &
914               presnivs(levmin(iff):levmax(iff)), nvertm(iff),"down")
915
916!!!!!!!!!!!!! Traitement des champs 3D pour histhf !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
917!!!!!!!!!!!!!!! A Revoir plus tard !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
918          !          IF (iff.eq.3.and.lev_files(iff).ge.4) THEN
919          !          CALL histbeg_phy("histhf3d",itau_phy, &
920          !     &                     zjulian, dtime, &
921          !     &                     nhorim, nid_hf3d)
922
923          !         CALL histvert(nid_hf3d, "presnivs", &
924          !     &                 "Vertical levels", "mb", &
925          !     &                 klev, presnivs/100., nvertm)
926          !          ENDIF
927          !
928!!!! Composentes de la coordonnee sigma-hybride
929          CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
930               levmax(iff) - levmin(iff) + 1,Ahyb,nvertap(iff))
931
932          CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
933               levmax(iff) - levmin(iff) + 1,Bhyb,nvertbp(iff))
934
935          CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &
936               levmax(iff) - levmin(iff) + 1,Alt,nvertAlt(iff))
937
938          !   CALL histvert(nid_files(iff), "preff","Reference pressure", "Pa", &
939          !                 1,preff,nvertp0(iff))
940!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
941          IF (.NOT.clef_stations(iff)) THEN
942             !
943             !IM: there is no way to have one single value in a netcdf file
944             !
945             type_ecri(1) = 'once'
946             type_ecri(2) = 'once'
947             type_ecri(3) = 'once'
948             type_ecri(4) = 'once'
949             type_ecri(5) = 'once'
950             type_ecri(6) = 'once'
951             CALL histdef2d(iff,clef_stations(iff),o_aire%flag,o_aire%name,"Grid area", "-")
952             CALL histdef2d(iff,clef_stations(iff),o_contfracATM%flag,o_contfracATM%name,"% sfce ter+lic", "-")
953          ENDIF
954          type_ecri(:) = type_ecri_files(:)
955
956!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
957          CALL histdef2d(iff,clef_stations(iff),o_phis%flag,o_phis%name,"Surface geop.height", "m2/s2" )
958          CALL histdef2d(iff,clef_stations(iff),o_contfracOR%flag,o_contfracOR%name,"% sfce terre OR", "-" )
959          CALL histdef2d(iff,clef_stations(iff),o_aireTER%flag,o_aireTER%name,"Grid area CONT", "-" )
960          CALL histdef2d(iff,clef_stations(iff),o_flat%flag,o_flat%name, "Latent heat flux", "W/m2")
961          CALL histdef2d(iff,clef_stations(iff),o_slp%flag,o_slp%name, "Sea Level Pressure", "Pa" )
962          CALL histdef2d(iff,clef_stations(iff),o_tsol%flag,o_tsol%name, "Surface Temperature", "K")
963          CALL histdef2d(iff,clef_stations(iff),o_t2m%flag,o_t2m%name, "Temperature 2m", "K" )
964          IF (.NOT.clef_stations(iff)) THEN
965             !
966             !IM: there is no way to have one single value in a netcdf file
967             !
968             type_ecri(1) = 't_min(X)'
969             type_ecri(2) = 't_min(X)'
970             type_ecri(3) = 't_min(X)'
971             type_ecri(4) = 't_min(X)'
972             type_ecri(5) = 't_min(X)'
973             type_ecri(6) = 't_min(X)'
974             CALL histdef2d(iff,clef_stations(iff),o_t2m_min%flag,o_t2m_min%name, "Temp 2m min", "K" )
975             type_ecri(1) = 't_max(X)'
976             type_ecri(2) = 't_max(X)'
977             type_ecri(3) = 't_max(X)'
978             type_ecri(4) = 't_max(X)'
979             type_ecri(5) = 't_max(X)'
980             type_ecri(6) = 't_max(X)'
981             CALL histdef2d(iff,clef_stations(iff),o_t2m_max%flag,o_t2m_max%name, "Temp 2m max", "K" )
982          ENDIF
983          type_ecri(:) = type_ecri_files(:)
984          CALL histdef2d(iff,clef_stations(iff),o_wind10m%flag,o_wind10m%name, "10-m wind speed", "m/s")
985          CALL histdef2d(iff,clef_stations(iff),o_wind10max%flag,o_wind10max%name, "10m wind speed max", "m/s")
986          CALL histdef2d(iff,clef_stations(iff),o_sicf%flag,o_sicf%name, "Sea-ice fraction", "-" )
987          CALL histdef2d(iff,clef_stations(iff),o_q2m%flag,o_q2m%name, "Specific humidity 2m", "kg/kg")
988          CALL histdef2d(iff,clef_stations(iff),o_ustar%flag,o_ustar%name, "Friction velocity", "m/s" )
989          CALL histdef2d(iff,clef_stations(iff),o_u10m%flag,o_u10m%name, "Vent zonal 10m", "m/s" )
990          CALL histdef2d(iff,clef_stations(iff),o_v10m%flag,o_v10m%name, "Vent meridien 10m", "m/s")
991          CALL histdef2d(iff,clef_stations(iff),o_psol%flag,o_psol%name, "Surface Pressure", "Pa" )
992          CALL histdef2d(iff,clef_stations(iff),o_qsurf%flag,o_qsurf%name, "Surface Air humidity", "kg/kg")
993
994          if (.not. ok_veget) then
995             CALL histdef2d(iff,clef_stations(iff),o_qsol%flag,o_qsol%name, "Soil watter content", "mm" )
996          endif
997
998             type_ecri(1) = 'inst(X)'
999             type_ecri(2) = 'inst(X)'
1000             type_ecri(3) = 'inst(X)'
1001             type_ecri(4) = 'inst(X)'
1002             type_ecri(5) = 'inst(X)'
1003             type_ecri(6) = 'inst(X)'
1004          CALL histdef2d(iff,clef_stations(iff),o_ndayrain%flag,o_ndayrain%name, "Number of dayrain(liq+sol)", "-")
1005             type_ecri(:) = type_ecri_files(:)
1006          CALL histdef2d(iff,clef_stations(iff),o_precip%flag,o_precip%name, "Precip Totale liq+sol", "kg/(s*m2)" )
1007          CALL histdef2d(iff,clef_stations(iff),o_plul%flag,o_plul%name, "Large-scale Precip.", "kg/(s*m2)")
1008          CALL histdef2d(iff,clef_stations(iff),o_pluc%flag,o_pluc%name, "Convective Precip.", "kg/(s*m2)")
1009          CALL histdef2d(iff,clef_stations(iff),o_snow%flag,o_snow%name, "Snow fall", "kg/(s*m2)" )
1010          CALL histdef2d(iff,clef_stations(iff),o_msnow%flag,o_msnow%name, "Surface snow amount", "kg/m2" )
1011          CALL histdef2d(iff,clef_stations(iff),o_fsnow%flag,o_fsnow%name, "Surface snow area fraction", "-" )
1012          CALL histdef2d(iff,clef_stations(iff),o_evap%flag,o_evap%name, "Evaporat", "kg/(s*m2)" )
1013          CALL histdef2d(iff,clef_stations(iff),o_tops%flag,o_tops%name, "Solar rad. at TOA", "W/m2")
1014          CALL histdef2d(iff,clef_stations(iff),o_tops0%flag,o_tops0%name, "CS Solar rad. at TOA", "W/m2")
1015          CALL histdef2d(iff,clef_stations(iff),o_topl%flag,o_topl%name, "IR rad. at TOA", "W/m2" )
1016          CALL histdef2d(iff,clef_stations(iff),o_topl0%flag,o_topl0%name, "IR rad. at TOA", "W/m2")
1017          CALL histdef2d(iff,clef_stations(iff),o_SWupTOA%flag,o_SWupTOA%name, "SWup at TOA", "W/m2")
1018          CALL histdef2d(iff,clef_stations(iff),o_SWupTOAclr%flag,o_SWupTOAclr%name, "SWup clear sky at TOA", "W/m2")
1019          CALL histdef2d(iff,clef_stations(iff),o_SWdnTOA%flag,o_SWdnTOA%name, "SWdn at TOA", "W/m2" )
1020          CALL histdef2d(iff,clef_stations(iff),o_SWdnTOAclr%flag,o_SWdnTOAclr%name, "SWdn clear sky at TOA", "W/m2")
1021          CALL histdef2d(iff,clef_stations(iff),o_nettop%flag,o_nettop%name, "Net dn radiatif flux at TOA", "W/m2")
1022          CALL histdef2d(iff,clef_stations(iff),o_SWup200%flag,o_SWup200%name, "SWup at 200mb", "W/m2" )
1023          CALL histdef2d(iff,clef_stations(iff),o_SWup200clr%flag,o_SWup200clr%name, "SWup clear sky at 200mb", "W/m2")
1024          CALL histdef2d(iff,clef_stations(iff),o_SWdn200%flag,o_SWdn200%name, "SWdn at 200mb", "W/m2" )
1025          CALL histdef2d(iff,clef_stations(iff),o_SWdn200clr%flag,o_SWdn200clr%name, "SWdn clear sky at 200mb", "W/m2")
1026          CALL histdef2d(iff,clef_stations(iff),o_LWup200%flag,o_LWup200%name, "LWup at 200mb", "W/m2")
1027          CALL histdef2d(iff,clef_stations(iff),o_LWup200clr%flag,o_LWup200clr%name, "LWup clear sky at 200mb", "W/m2")
1028          CALL histdef2d(iff,clef_stations(iff),o_LWdn200%flag,o_LWdn200%name, "LWdn at 200mb", "W/m2")
1029          CALL histdef2d(iff,clef_stations(iff),o_LWdn200clr%flag,o_LWdn200clr%name, "LWdn clear sky at 200mb", "W/m2")
1030          CALL histdef2d(iff,clef_stations(iff),o_sols%flag,o_sols%name, "Solar rad. at surf.", "W/m2")
1031          CALL histdef2d(iff,clef_stations(iff),o_sols0%flag,o_sols0%name, "Solar rad. at surf.", "W/m2")
1032          CALL histdef2d(iff,clef_stations(iff),o_soll%flag,o_soll%name, "IR rad. at surface", "W/m2") 
1033          CALL histdef2d(iff,clef_stations(iff),o_radsol%flag,o_radsol%name, "Rayonnement au sol", "W/m2")
1034          CALL histdef2d(iff,clef_stations(iff),o_soll0%flag,o_soll0%name, "IR rad. at surface", "W/m2")
1035          CALL histdef2d(iff,clef_stations(iff),o_SWupSFC%flag,o_SWupSFC%name, "SWup at surface", "W/m2")
1036          CALL histdef2d(iff,clef_stations(iff),o_SWupSFCclr%flag,o_SWupSFCclr%name, "SWup clear sky at surface", "W/m2")
1037          CALL histdef2d(iff,clef_stations(iff),o_SWdnSFC%flag,o_SWdnSFC%name, "SWdn at surface", "W/m2")
1038          CALL histdef2d(iff,clef_stations(iff),o_SWdnSFCclr%flag,o_SWdnSFCclr%name, "SWdn clear sky at surface", "W/m2")
1039          CALL histdef2d(iff,clef_stations(iff),o_LWupSFC%flag,o_LWupSFC%name, "Upwd. IR rad. at surface", "W/m2")
1040          CALL histdef2d(iff,clef_stations(iff),o_LWdnSFC%flag,o_LWdnSFC%name, "Down. IR rad. at surface", "W/m2")
1041          CALL histdef2d(iff,clef_stations(iff),o_LWupSFCclr%flag,o_LWupSFCclr%name, "CS Upwd. IR rad. at surface", "W/m2")
1042          CALL histdef2d(iff,clef_stations(iff),o_LWdnSFCclr%flag,o_LWdnSFCclr%name, "Down. CS IR rad. at surface", "W/m2")
1043          CALL histdef2d(iff,clef_stations(iff),o_bils%flag,o_bils%name, "Surf. total heat flux", "W/m2")
1044          CALL histdef2d(iff,clef_stations(iff),o_bils_ec%flag,o_bils_ec%name, "Surf. total heat flux", "W/m2")
1045          CALL histdef2d(iff,clef_stations(iff),o_bils_kinetic%flag,o_bils_kinetic%name, "Surf. total heat flux", "W/m2")
1046          CALL histdef2d(iff,clef_stations(iff),o_bils_enthalp%flag,o_bils_enthalp%name, "Surf. total heat flux", "W/m2")
1047          CALL histdef2d(iff,clef_stations(iff),o_bils_latent%flag,o_bils_latent%name, "Surf. total heat flux", "W/m2")
1048          CALL histdef2d(iff,clef_stations(iff),o_sens%flag,o_sens%name, "Sensible heat flux", "W/m2")
1049          CALL histdef2d(iff,clef_stations(iff),o_fder%flag,o_fder%name, "Heat flux derivation", "W/m2")
1050          CALL histdef2d(iff,clef_stations(iff),o_ffonte%flag,o_ffonte%name, "Thermal flux for snow melting", "W/m2")
1051          CALL histdef2d(iff,clef_stations(iff),o_fqcalving%flag,o_fqcalving%name, "Ice Calving", "kg/m2/s")
1052          CALL histdef2d(iff,clef_stations(iff),o_fqfonte%flag,o_fqfonte%name, "Land ice melt", "kg/m2/s")
1053
1054          CALL histdef2d(iff,clef_stations(iff),o_taux%flag,o_taux%name, "Zonal wind stress","Pa")
1055          CALL histdef2d(iff,clef_stations(iff),o_tauy%flag,o_tauy%name, "Meridional wind stress","Pa")
1056
1057          DO nsrf = 1, nbsrf
1058             CALL histdef2d(iff,clef_stations(iff),o_pourc_srf(nsrf)%flag,o_pourc_srf(nsrf)%name,"% "//clnsurf(nsrf),"%")
1059             CALL histdef2d(iff,clef_stations(iff),o_fract_srf(nsrf)%flag,o_fract_srf(nsrf)%name,"Fraction "//clnsurf(nsrf),"1")
1060             CALL histdef2d(iff,clef_stations(iff), &
1061                  o_taux_srf(nsrf)%flag,o_taux_srf(nsrf)%name,"Zonal wind stress"//clnsurf(nsrf),"Pa")
1062             CALL histdef2d(iff,clef_stations(iff), &
1063                  o_tauy_srf(nsrf)%flag,o_tauy_srf(nsrf)%name,"Meridional wind stress "//clnsurf(nsrf),"Pa")
1064             CALL histdef2d(iff,clef_stations(iff), &
1065                  o_tsol_srf(nsrf)%flag,o_tsol_srf(nsrf)%name,"Temperature "//clnsurf(nsrf),"K")
1066             CALL histdef2d(iff,clef_stations(iff), &
1067                  o_evappot_srf(nsrf)%flag,o_evappot_srf(nsrf)%name,"Temperature"//clnsurf(nsrf),"K")
1068             CALL histdef2d(iff,clef_stations(iff), &
1069                  o_ustar_srf(nsrf)%flag,o_ustar_srf(nsrf)%name,"Friction velocity "//clnsurf(nsrf),"m/s")
1070             CALL histdef2d(iff,clef_stations(iff), &
1071                  o_u10m_srf(nsrf)%flag,o_u10m_srf(nsrf)%name,"Vent Zonal 10m "//clnsurf(nsrf),"m/s")
1072             CALL histdef2d(iff,clef_stations(iff), &
1073                  o_evap_srf(nsrf)%flag,o_evap_srf(nsrf)%name,"evaporation at surface "//clnsurf(nsrf),"kg/(s*m2)")
1074             CALL histdef2d(iff,clef_stations(iff), &
1075                  o_v10m_srf(nsrf)%flag,o_v10m_srf(nsrf)%name,"Vent meredien 10m "//clnsurf(nsrf),"m/s")
1076             CALL histdef2d(iff,clef_stations(iff), &
1077                  o_t2m_srf(nsrf)%flag,o_t2m_srf(nsrf)%name,"Temp 2m "//clnsurf(nsrf),"K")
1078             CALL histdef2d(iff,clef_stations(iff), &
1079                  o_sens_srf(nsrf)%flag,o_sens_srf(nsrf)%name,"Sensible heat flux "//clnsurf(nsrf),"W/m2")
1080             CALL histdef2d(iff,clef_stations(iff), &
1081                  o_lat_srf(nsrf)%flag,o_lat_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
1082             CALL histdef2d(iff,clef_stations(iff), &
1083                  o_flw_srf(nsrf)%flag,o_flw_srf(nsrf)%name,"LW "//clnsurf(nsrf),"W/m2")
1084             CALL histdef2d(iff,clef_stations(iff), &
1085                  o_fsw_srf(nsrf)%flag,o_fsw_srf(nsrf)%name,"SW "//clnsurf(nsrf),"W/m2")
1086             CALL histdef2d(iff,clef_stations(iff), &
1087                  o_wbils_srf(nsrf)%flag,o_wbils_srf(nsrf)%name,"Bilan sol "//clnsurf(nsrf),"W/m2" )
1088             CALL histdef2d(iff,clef_stations(iff), &
1089                  o_wbilo_srf(nsrf)%flag,o_wbilo_srf(nsrf)%name,"Bilan eau "//clnsurf(nsrf),"kg/(m2*s)")
1090             if (iflag_pbl>1 .and. lev_files(iff).gt.10 ) then
1091                CALL histdef2d(iff,clef_stations(iff), &
1092                     o_tke_srf(nsrf)%flag,o_tke_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
1093
1094                IF (.NOT.clef_stations(iff)) THEN
1095                   !
1096                   !IM: there is no way to have one single value in a netcdf file
1097                   !
1098                   type_ecri(1) = 't_max(X)'
1099                   type_ecri(2) = 't_max(X)'
1100                   type_ecri(3) = 't_max(X)'
1101                   type_ecri(4) = 't_max(X)'
1102                   type_ecri(5) = 't_max(X)'
1103                   type_ecri(6) = 't_max(X)'
1104                   CALL histdef2d(iff,clef_stations(iff), &
1105                        o_tke_max_srf(nsrf)%flag,o_tke_max_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
1106                   type_ecri(:) = type_ecri_files(:)
1107                ENDIF
1108
1109             endif
1110
1111             CALL histdef2d(iff,clef_stations(iff), &
1112                  o_albe_srf(nsrf)%flag,o_albe_srf(nsrf)%name,"Albedo VIS surf. "//clnsurf(nsrf),"-")
1113             CALL histdef2d(iff,clef_stations(iff), &
1114                  o_rugs_srf(nsrf)%flag,o_rugs_srf(nsrf)%name,"Surface roughness "//clnsurf(nsrf),"m")
1115             CALL histdef2d(iff,clef_stations(iff), &
1116                  o_ages_srf(nsrf)%flag,o_ages_srf(nsrf)%name,"Snow age", "day")
1117          END DO
1118
1119          IF (new_aod .AND. (.NOT. aerosol_couple)) THEN
1120             IF (ok_ade.OR.ok_aie) THEN
1121
1122                CALL histdef2d(iff,clef_stations(iff), &
1123                     o_od550aer%flag,o_od550aer%name, "Total aerosol optical depth at 550nm", "-")
1124                CALL histdef2d(iff,clef_stations(iff), &
1125                     o_od865aer%flag,o_od865aer%name, "Total aerosol optical depth at 870nm", "-")
1126                CALL histdef2d(iff,clef_stations(iff), &
1127                     o_absvisaer%flag,o_absvisaer%name, "Absorption aerosol visible optical depth", "-")
1128                CALL histdef2d(iff,clef_stations(iff), &
1129                     o_od550lt1aer%flag,o_od550lt1aer%name, "Fine mode optical depth", "-")
1130
1131
1132                CALL histdef2d(iff,clef_stations(iff), &
1133                     o_sconcso4%flag,o_sconcso4%name,"Surface Concentration of Sulfate ","kg/m3")
1134                CALL histdef2d(iff,clef_stations(iff), &
1135                     o_sconcoa%flag,o_sconcoa%name,"Surface Concentration of Organic Aerosol ","kg/m3")
1136                CALL histdef2d(iff,clef_stations(iff), &
1137                     o_sconcbc%flag,o_sconcbc%name,"Surface Concentration of Black Carbon ","kg/m3")
1138                CALL histdef2d(iff,clef_stations(iff), &
1139                     o_sconcss%flag,o_sconcss%name,"Surface Concentration of Sea Salt ","kg/m3")
1140                CALL histdef2d(iff,clef_stations(iff), &
1141                     o_sconcdust%flag,o_sconcdust%name,"Surface Concentration of Dust ","kg/m3")
1142                CALL histdef3d(iff,clef_stations(iff), &
1143                     o_concso4%flag,o_concso4%name,"Concentration of Sulfate ","kg/m3")
1144                CALL histdef3d(iff,clef_stations(iff), &
1145                     o_concoa%flag,o_concoa%name,"Concentration of Organic Aerosol ","kg/m3")
1146                CALL histdef3d(iff,clef_stations(iff), &
1147                     o_concbc%flag,o_concbc%name,"Concentration of Black Carbon ","kg/m3")
1148                CALL histdef3d(iff,clef_stations(iff), &
1149                     o_concss%flag,o_concss%name,"Concentration of Sea Salt ","kg/m3")
1150                CALL histdef3d(iff,clef_stations(iff), &
1151                     o_concdust%flag,o_concdust%name,"Concentration of Dust ","kg/m3")
1152                CALL histdef2d(iff,clef_stations(iff), &
1153                     o_loadso4%flag,o_loadso4%name,"Column Load of Sulfate ","kg/m2")
1154                CALL histdef2d(iff,clef_stations(iff), &
1155                     o_loadoa%flag,o_loadoa%name,"Column Load of Organic Aerosol ","kg/m2")
1156                CALL histdef2d(iff,clef_stations(iff), &
1157                     o_loadbc%flag,o_loadbc%name,"Column Load of Black Carbon ","kg/m2")
1158                CALL histdef2d(iff,clef_stations(iff), &
1159                     o_loadss%flag,o_loadss%name,"Column Load of Sea Salt ","kg/m2")
1160                CALL histdef2d(iff,clef_stations(iff), &
1161                     o_loaddust%flag,o_loaddust%name,"Column Load of Dust ","kg/m2")
1162
1163                DO naero = 1, naero_spc
1164                   CALL histdef2d(iff,clef_stations(iff), &
1165                        o_tausumaero(naero)%flag,o_tausumaero(naero)%name,"Aerosol Optical depth at 550 nm "//name_aero(naero),"1")
1166                END DO
1167             ENDIF
1168          ENDIF
1169
1170          IF (ok_ade) THEN
1171             CALL histdef2d(iff,clef_stations(iff), &
1172                  o_topswad%flag,o_topswad%name, "ADE at TOA", "W/m2")
1173             CALL histdef2d(iff,clef_stations(iff), &
1174                  o_topswad0%flag,o_topswad0%name, "ADE clear-sky at TOA", "W/m2")
1175             CALL histdef2d(iff,clef_stations(iff), &
1176                  o_solswad%flag,o_solswad%name, "ADE at SRF", "W/m2")
1177             CALL histdef2d(iff,clef_stations(iff), &
1178                  o_solswad0%flag,o_solswad0%name, "ADE clear-sky at SRF", "W/m2")
1179
1180             CALL histdef2d(iff,clef_stations(iff), &
1181                  o_swtoaas_nat%flag,o_swtoaas_nat%name, "Natural aerosol radiative forcing all-sky at TOA", "W/m2")
1182             CALL histdef2d(iff,clef_stations(iff), &
1183                  o_swsrfas_nat%flag,o_swsrfas_nat%name, "Natural aerosol radiative forcing all-sky at SRF", "W/m2")
1184             CALL histdef2d(iff,clef_stations(iff), &
1185                  o_swtoacs_nat%flag,o_swtoacs_nat%name, "Natural aerosol radiative forcing clear-sky at TOA", "W/m2")
1186             CALL histdef2d(iff,clef_stations(iff), &
1187                  o_swsrfcs_nat%flag,o_swsrfcs_nat%name, "Natural aerosol radiative forcing clear-sky at SRF", "W/m2")
1188
1189             CALL histdef2d(iff,clef_stations(iff), &
1190                  o_swtoaas_ant%flag,o_swtoaas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at TOA", "W/m2")
1191             CALL histdef2d(iff,clef_stations(iff), &
1192                  o_swsrfas_ant%flag,o_swsrfas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at SRF", "W/m2")
1193             CALL histdef2d(iff,clef_stations(iff), &
1194                  o_swtoacs_ant%flag,o_swtoacs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at TOA", "W/m2")
1195             CALL histdef2d(iff,clef_stations(iff), &
1196                  o_swsrfcs_ant%flag,o_swsrfcs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at SRF", "W/m2")
1197
1198             IF (.NOT. aerosol_couple) THEN
1199                CALL histdef2d(iff,clef_stations(iff), &
1200                     o_swtoacf_nat%flag,o_swtoacf_nat%name, "Natural aerosol impact on cloud radiative forcing at TOA", "W/m2")
1201                CALL histdef2d(iff,clef_stations(iff), &
1202                     o_swsrfcf_nat%flag,o_swsrfcf_nat%name, "Natural aerosol impact on cloud radiative forcing  at SRF", "W/m2")
1203                CALL histdef2d(iff, clef_stations(iff), o_swtoacf_ant%flag, &
1204                     o_swtoacf_ant%name, &
1205                     "Anthropogenic aerosol impact on cloud radiative forcing at TOA", &
1206                     "W/m2")
1207                CALL histdef2d(iff, clef_stations(iff), o_swsrfcf_ant%flag, &
1208                     o_swsrfcf_ant%name, &
1209                     "Anthropogenic aerosol impact on cloud radiative forcing at SRF", &
1210                     "W/m2")
1211                CALL histdef2d(iff,clef_stations(iff), &
1212                     o_swtoacf_zero%flag,o_swtoacf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at TOA", "W/m2")
1213                CALL histdef2d(iff,clef_stations(iff), &
1214                     o_swsrfcf_zero%flag,o_swsrfcf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at SRF", "W/m2")
1215             ENDIF
1216          ENDIF
1217
1218          IF (ok_aie) THEN
1219             CALL histdef2d(iff,clef_stations(iff), &
1220                  o_topswai%flag,o_topswai%name, "AIE at TOA", "W/m2")
1221             CALL histdef2d(iff,clef_stations(iff), &
1222                  o_solswai%flag,o_solswai%name, "AIE at SFR", "W/m2")
1223             !Cloud droplet number concentration
1224             CALL histdef3d(iff,clef_stations(iff), &
1225                  o_scdnc%flag,o_scdnc%name, "Cloud droplet number concentration","m-3")
1226             CALL histdef2d(iff,clef_stations(iff), &
1227                  o_cldncl%flag,o_cldncl%name, "CDNC at top of liquid water cloud", "m-3")
1228             CALL histdef3d(iff,clef_stations(iff), &
1229                  o_reffclws%flag,o_reffclws%name, "Stratiform Cloud Droplet Effective Radius (aerosol diags.)","m")
1230             CALL histdef3d(iff,clef_stations(iff), &
1231                  o_reffclwc%flag,o_reffclwc%name, "Convective Cloud Droplet Effective Radius (aerosol diags.)","m")
1232             CALL histdef2d(iff,clef_stations(iff), &
1233                  o_cldnvi%flag,o_cldnvi%name, "Column Integrated Cloud Droplet Number", "m-2")
1234             CALL histdef3d(iff,clef_stations(iff), &
1235                  o_lcc3d%flag,o_lcc3d%name, "Cloud liquid fraction","1")
1236             CALL histdef3d(iff,clef_stations(iff), &
1237                  o_lcc3dcon%flag,o_lcc3dcon%name, "Convective cloud liquid fraction","1")
1238             CALL histdef3d(iff,clef_stations(iff), &
1239                  o_lcc3dstra%flag,o_lcc3dstra%name, "Stratiform cloud liquid fraction","1")
1240             CALL histdef2d(iff,clef_stations(iff), &
1241                  o_lcc%flag,o_lcc%name, "Cloud liquid fraction at top of cloud","1")
1242             CALL histdef2d(iff,clef_stations(iff), &
1243                  o_reffclwtop%flag,o_reffclwtop%name, "Droplet effective radius at top of liquid water cloud", "m")
1244          ENDIF
1245
1246
1247          CALL histdef2d(iff,clef_stations(iff), &
1248               o_alb1%flag,o_alb1%name, "Surface VIS albedo", "-")
1249          CALL histdef2d(iff,clef_stations(iff), &
1250               o_alb2%flag,o_alb2%name, "Surface Near IR albedo", "-")
1251          CALL histdef2d(iff,clef_stations(iff), &
1252               o_cdrm%flag,o_cdrm%name, "Momentum drag coef.", "-")
1253          CALL histdef2d(iff,clef_stations(iff), &
1254               o_cdrh%flag,o_cdrh%name, "Heat drag coef.", "-" )
1255          CALL histdef2d(iff,clef_stations(iff), &
1256               o_cldl%flag,o_cldl%name, "Low-level cloudiness", "-")
1257          CALL histdef2d(iff,clef_stations(iff), &
1258               o_cldm%flag,o_cldm%name, "Mid-level cloudiness", "-")
1259          CALL histdef2d(iff,clef_stations(iff), &
1260               o_cldh%flag,o_cldh%name, "High-level cloudiness", "-")
1261          CALL histdef2d(iff,clef_stations(iff), &
1262               o_cldt%flag,o_cldt%name, "Total cloudiness", "-")
1263          CALL histdef2d(iff,clef_stations(iff), &
1264               o_cldq%flag,o_cldq%name, "Cloud liquid water path", "kg/m2")
1265          CALL histdef2d(iff,clef_stations(iff), &
1266               o_lwp%flag,o_lwp%name, "Cloud water path", "kg/m2")
1267          CALL histdef2d(iff,clef_stations(iff), &
1268               o_iwp%flag,o_iwp%name, "Cloud ice water path", "kg/m2" )
1269          CALL histdef2d(iff,clef_stations(iff), &
1270               o_ue%flag,o_ue%name, "Zonal energy transport", "-")
1271          CALL histdef2d(iff,clef_stations(iff), &
1272               o_ve%flag,o_ve%name, "Merid energy transport", "-")
1273          CALL histdef2d(iff,clef_stations(iff), &
1274               o_uq%flag,o_uq%name, "Zonal humidity transport", "-")
1275          CALL histdef2d(iff,clef_stations(iff), &
1276               o_vq%flag,o_vq%name, "Merid humidity transport", "-")
1277
1278          IF(iflag_con.GE.3) THEN ! sb
1279             CALL histdef2d(iff,clef_stations(iff), &
1280                  o_cape%flag,o_cape%name, "Conv avlbl pot ener", "J/kg")
1281             CALL histdef2d(iff,clef_stations(iff), &
1282                  o_pbase%flag,o_pbase%name, "Cld base pressure", "Pa")
1283             CALL histdef2d(iff,clef_stations(iff), &
1284                  o_ptop%flag,o_ptop%name, "Cld top pressure", "Pa")
1285             CALL histdef2d(iff,clef_stations(iff), &
1286                  o_fbase%flag,o_fbase%name, "Cld base mass flux", "kg/m2/s")
1287             if (iflag_con /= 30) then
1288                CALL histdef2d(iff,clef_stations(iff), &
1289                     o_plcl%flag,o_plcl%name, "Lifting Condensation Level", "hPa")
1290                CALL histdef2d(iff,clef_stations(iff), &
1291                     o_plfc%flag,o_plfc%name, "Level of Free Convection", "hPa")
1292                CALL histdef2d(iff,clef_stations(iff), &
1293                     o_wbeff%flag,o_wbeff%name, "Conv. updraft velocity at LFC (<100)", "m/s")
1294             end if
1295             IF (.NOT.clef_stations(iff)) THEN
1296                !
1297                !IM: there is no way to have one single value in a netcdf file
1298                !
1299                type_ecri(1) = 't_max(X)'
1300                type_ecri(2) = 't_max(X)'
1301                type_ecri(3) = 't_max(X)'
1302                type_ecri(4) = 't_max(X)'
1303                type_ecri(5) = 't_max(X)'
1304                type_ecri(6) = 't_max(X)'
1305                CALL histdef2d(iff,clef_stations(iff), &
1306                     o_cape_max%flag,o_cape_max%name, "CAPE max.", "J/kg")
1307             ENDIF
1308             type_ecri(:) = type_ecri_files(:)
1309             CALL histdef3d(iff,clef_stations(iff), &
1310                  o_upwd%flag,o_upwd%name, "saturated updraft", "kg/m2/s")
1311             CALL histdef3d(iff,clef_stations(iff), &
1312                  o_Ma%flag,o_Ma%name, "undilute adiab updraft", "kg/m2/s")
1313             CALL histdef3d(iff,clef_stations(iff), &
1314                  o_dnwd%flag,o_dnwd%name, "saturated downdraft", "kg/m2/s")
1315             CALL histdef3d(iff,clef_stations(iff), &
1316                  o_dnwd0%flag,o_dnwd0%name, "unsat. downdraft", "kg/m2/s")
1317             CALL histdef3d(iff,clef_stations(iff), &
1318                  o_mc%flag,o_mc%name, "Convective mass flux", "kg/m2/s")
1319             type_ecri(1) = 'inst(X)'
1320             type_ecri(2) = 'inst(X)'
1321             type_ecri(3) = 'inst(X)'
1322             type_ecri(4) = 'inst(X)'
1323             type_ecri(5) = 'inst(X)'
1324             type_ecri(6) = 'inst(X)'
1325             CALL histdef2d(iff,clef_stations(iff), &
1326                  o_ftime_con%flag,o_ftime_con%name, "Fraction of time convection Occurs", " ")
1327             type_ecri(:) = type_ecri_files(:)
1328          ENDIF !iflag_con .GE. 3
1329
1330          CALL histdef2d(iff,clef_stations(iff), &
1331               o_prw%flag,o_prw%name, "Precipitable water", "kg/m2")
1332          CALL histdef2d(iff,clef_stations(iff), &
1333               o_s_pblh%flag,o_s_pblh%name, "Boundary Layer Height", "m")
1334          CALL histdef2d(iff,clef_stations(iff), &
1335               o_s_pblt%flag,o_s_pblt%name, "t at Boundary Layer Height", "K")
1336          CALL histdef2d(iff,clef_stations(iff), &
1337               o_s_lcl%flag,o_s_lcl%name, "Condensation level", "m")
1338          CALL histdef2d(iff,clef_stations(iff), &
1339               o_s_therm%flag,o_s_therm%name, "Exces du thermique", "K")
1340          !IM : Les champs suivants (s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F
1341          !CALL histdef2d(iff,clef_stations(iff), &
1342          !o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" )
1343          !CALL histdef2d(iff,clef_stations(iff), &
1344          !o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2")
1345          !CALL histdef2d(iff,clef_stations(iff), &
1346          !o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K")
1347          !CALL histdef2d(iff,clef_stations(iff), &
1348          !o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2")
1349          !CALL histdef2d(iff,clef_stations(iff), &
1350          !o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2")
1351          !CALL histdef2d(iff,clef_stations(iff), &
1352          !o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m")
1353
1354          ! Champs interpolles sur des niveaux de pression
1355
1356          type_ecri(1) = 'inst(X)'
1357          type_ecri(2) = 'inst(X)'
1358          type_ecri(3) = 'inst(X)'
1359          type_ecri(4) = 'inst(X)'
1360          type_ecri(5) = 'inst(X)'
1361          type_ecri(6) = 'inst(X)'
1362
1363          ! Attention a reverifier
1364
1365          ilev=0       
1366          DO k=1, nlevSTD
1367             bb2=clevSTD(k)
1368             IF(bb2.EQ."850".OR.bb2.EQ."700".OR.bb2.EQ."500".OR.bb2.EQ."200" &
1369                  .OR.bb2.EQ."100".OR.bb2.EQ."50".OR.bb2.EQ."10")THEN
1370                ilev=ilev+1
1371                !     print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name
1372                CALL histdef2d(iff,clef_stations(iff), &
1373                     o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name,"Zonal wind "//bb2//"hPa", "m/s")
1374                CALL histdef2d(iff,clef_stations(iff), &
1375                     o_vSTDlevs(ilev)%flag,o_vSTDlevs(ilev)%name,"Meridional wind "//bb2//"hPa", "m/s")
1376                CALL histdef2d(iff,clef_stations(iff), &
1377                     o_wSTDlevs(ilev)%flag,o_wSTDlevs(ilev)%name,"Vertical wind "//bb2//"hPa", "Pa/s")
1378                CALL histdef2d(iff,clef_stations(iff), &
1379                     o_zSTDlevs(ilev)%flag,o_zSTDlevs(ilev)%name,"Geopotential height "//bb2//"hPa", "m")
1380                CALL histdef2d(iff,clef_stations(iff), &
1381                     o_qSTDlevs(ilev)%flag,o_qSTDlevs(ilev)%name,"Specific humidity "//bb2//"hPa", "kg/kg" )
1382                CALL histdef2d(iff,clef_stations(iff), &
1383                     o_tSTDlevs(ilev)%flag,o_tSTDlevs(ilev)%name,"Temperature "//bb2//"hPa", "K")
1384             ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")
1385          ENDDO
1386          type_ecri(:) = type_ecri_files(:)
1387
1388          CALL histdef2d(iff,clef_stations(iff), &
1389               o_t_oce_sic%flag,o_t_oce_sic%name, "Temp mixte oce-sic", "K")
1390
1391          IF (type_ocean=='slab') &
1392               CALL histdef2d(iff,clef_stations(iff), &
1393               o_slab_bils%flag, o_slab_bils%name,"Bilan au sol sur ocean slab", "W/m2")
1394
1395          ! Couplage conv-CL
1396          IF (iflag_con.GE.3) THEN
1397             IF (iflag_coupl>=1) THEN
1398                CALL histdef2d(iff,clef_stations(iff), &
1399                     o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2")
1400                CALL histdef2d(iff,clef_stations(iff), &
1401                     o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2")
1402             ENDIF
1403          ENDIF !(iflag_con.GE.3)
1404
1405          CALL histdef2d(iff,clef_stations(iff), &
1406               o_weakinv%flag,o_weakinv%name, "Weak inversion", "-")
1407          CALL histdef2d(iff,clef_stations(iff), &
1408               o_dthmin%flag,o_dthmin%name, "dTheta mini", "K/m")
1409          CALL histdef2d(iff,clef_stations(iff), &
1410               o_rh2m%flag,o_rh2m%name, "Relative humidity at 2m", "%" )
1411
1412          IF (.NOT.clef_stations(iff)) THEN
1413             !
1414             !IM: there is no way to have one single value in a netcdf file
1415             !
1416             type_ecri(1) = 't_min(X)'
1417             type_ecri(2) = 't_min(X)'
1418             type_ecri(3) = 't_min(X)'
1419             type_ecri(4) = 't_min(X)'
1420             type_ecri(5) = 't_min(X)'
1421             type_ecri(6) = 't_min(X)'
1422             CALL histdef2d(iff,clef_stations(iff),o_rh2m_min%flag,o_rh2m_min%name, "Min Relative humidity at 2m", "%" )
1423             type_ecri(1) = 't_max(X)'
1424             type_ecri(2) = 't_max(X)'
1425             type_ecri(3) = 't_max(X)'
1426             type_ecri(4) = 't_max(X)'
1427             type_ecri(5) = 't_max(X)'
1428             type_ecri(6) = 't_max(X)'
1429             CALL histdef2d(iff,clef_stations(iff),o_rh2m_max%flag,o_rh2m_max%name, "Max Relative humidity at 2m", "%" )
1430          ENDIF
1431
1432          type_ecri(:) = type_ecri_files(:)
1433          CALL histdef2d(iff,clef_stations(iff),o_qsat2m%flag,o_qsat2m%name, "Saturant humidity at 2m", "%")
1434          CALL histdef2d(iff,clef_stations(iff),o_tpot%flag,o_tpot%name, "Surface air potential temperature", "K")
1435          CALL histdef2d(iff,clef_stations(iff), &
1436               o_tpote%flag,o_tpote%name, "Surface air equivalent potential temperature", "K")
1437          CALL histdef2d(iff,clef_stations(iff),o_SWnetOR%flag,o_SWnetOR%name, "Sfce net SW radiation OR", "W/m2")
1438          CALL histdef2d(iff,clef_stations(iff),o_SWdownOR%flag,o_SWdownOR%name, "Sfce incident SW radiation OR", "W/m2")
1439          CALL histdef2d(iff,clef_stations(iff),o_LWdownOR%flag,o_LWdownOR%name, "Sfce incident LW radiation OR", "W/m2")
1440          CALL histdef2d(iff,clef_stations(iff),o_snowl%flag,o_snowl%name, "Solid Large-scale Precip.", "kg/(m2*s)")
1441
1442          CALL histdef2d(iff,clef_stations(iff),o_solldown%flag,o_solldown%name, "Down. IR rad. at surface", "W/m2")
1443          CALL histdef2d(iff,clef_stations(iff),o_dtsvdfo%flag,o_dtsvdfo%name, "Boundary-layer dTs(o)", "K/s")
1444          CALL histdef2d(iff,clef_stations(iff),o_dtsvdft%flag,o_dtsvdft%name, "Boundary-layer dTs(t)", "K/s")
1445          CALL histdef2d(iff,clef_stations(iff),o_dtsvdfg%flag,o_dtsvdfg%name, "Boundary-layer dTs(g)", "K/s")
1446          CALL histdef2d(iff,clef_stations(iff),o_dtsvdfi%flag,o_dtsvdfi%name, "Boundary-layer dTs(g)", "K/s")
1447          CALL histdef2d(iff,clef_stations(iff),o_rugs%flag,o_rugs%name, "rugosity", "-" )
1448
1449          ! Champs 3D:
1450          CALL histdef3d(iff,clef_stations(iff),o_ec550aer%flag,o_ec550aer%name, "Extinction at 550nm", "m^-1")
1451          CALL histdef3d(iff,clef_stations(iff),o_lwcon%flag,o_lwcon%name, "Cloud liquid water content", "kg/kg")
1452          CALL histdef3d(iff,clef_stations(iff),o_iwcon%flag,o_iwcon%name, "Cloud ice water content", "kg/kg")
1453          CALL histdef3d(iff,clef_stations(iff),o_temp%flag,o_temp%name, "Air temperature", "K" )
1454          CALL histdef3d(iff,clef_stations(iff),o_theta%flag,o_theta%name, "Potential air temperature", "K" )
1455          CALL histdef3d(iff,clef_stations(iff),o_ovap%flag,o_ovap%name, "Specific humidity", "kg/kg" )
1456          CALL histdef3d(iff,clef_stations(iff),o_oliq%flag,o_oliq%name, "Condensed water", "kg/kg" )
1457          CALL histdef3d(iff,clef_stations(iff), &
1458               o_ovapinit%flag,o_ovapinit%name, "Specific humidity (begin of timestep)", "kg/kg" )
1459          CALL histdef3d(iff,clef_stations(iff), &
1460               o_geop%flag,o_geop%name, "Geopotential height", "m2/s2")
1461          CALL histdef3d(iff,clef_stations(iff), &
1462               o_vitu%flag,o_vitu%name, "Zonal wind", "m/s" )
1463          CALL histdef3d(iff,clef_stations(iff), &
1464               o_vitv%flag,o_vitv%name, "Meridional wind", "m/s" )
1465          CALL histdef3d(iff,clef_stations(iff), &
1466               o_vitw%flag,o_vitw%name, "Vertical wind", "Pa/s" )
1467          CALL histdef3d(iff,clef_stations(iff), &
1468               o_pres%flag,o_pres%name, "Air pressure", "Pa" )
1469          CALL histdef3d(iff,clef_stations(iff), &
1470               o_paprs%flag,o_paprs%name, "Air pressure Inter-Couches", "Pa" )
1471          CALL histdef3d(iff,clef_stations(iff), &
1472               o_mass%flag,o_mass%name, "Masse Couches", "kg/m2" )
1473          CALL histdef3d(iff,clef_stations(iff), &
1474               o_zfull%flag,o_zfull%name, "Altitude of full pressure levels", "m" )
1475          CALL histdef3d(iff,clef_stations(iff), &
1476               o_zhalf%flag,o_zhalf%name, "Altitude of half pressure levels", "m" )
1477          CALL histdef3d(iff,clef_stations(iff), &
1478               o_rneb%flag,o_rneb%name, "Cloud fraction", "-")
1479          CALL histdef3d(iff,clef_stations(iff), &
1480               o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-")
1481          CALL histdef3d(iff,clef_stations(iff), &
1482               o_rnebls%flag,o_rnebls%name, "LS Cloud fraction", "-")
1483          CALL histdef3d(iff,clef_stations(iff), &
1484               o_rhum%flag,o_rhum%name, "Relative humidity", "-")
1485          CALL histdef3d(iff,clef_stations(iff), &
1486               o_ozone%flag,o_ozone%name, "Ozone mole fraction", "-")
1487          if (read_climoz == 2) &
1488               CALL histdef3d(iff,clef_stations(iff), &
1489               o_ozone_light%flag,o_ozone_light%name, &
1490               "Daylight ozone mole fraction", "-")
1491          CALL histdef3d(iff,clef_stations(iff), &
1492               o_dtphy%flag,o_dtphy%name, "Physics dT", "K/s")
1493          CALL histdef3d(iff,clef_stations(iff), &
1494               o_dqphy%flag,o_dqphy%name, "Physics dQ", "(kg/kg)/s")
1495          CALL histdef3d(iff,clef_stations(iff), &
1496               o_cldtau%flag,o_cldtau%name, "Cloud optical thickness", "1")
1497          CALL histdef3d(iff,clef_stations(iff), &
1498               o_cldemi%flag,o_cldemi%name, "Cloud optical emissivity", "1")
1499          !IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl
1500          CALL histdef3d(iff,clef_stations(iff), &
1501               o_pr_con_l%flag,o_pr_con_l%name, "Convective precipitation lic", " ")
1502          CALL histdef3d(iff,clef_stations(iff), &
1503               o_pr_con_i%flag,o_pr_con_i%name, "Convective precipitation ice", " ")
1504          CALL histdef3d(iff,clef_stations(iff), &
1505               o_pr_lsc_l%flag,o_pr_lsc_l%name, "Large scale precipitation lic", " ")
1506          CALL histdef3d(iff,clef_stations(iff), &
1507               o_pr_lsc_i%flag,o_pr_lsc_i%name, "Large scale precipitation ice", " ")
1508          !Cloud droplet effective radius
1509          CALL histdef3d(iff,clef_stations(iff), &
1510               o_re%flag,o_re%name, "Cloud droplet effective radius","um")
1511          CALL histdef3d(iff,clef_stations(iff), &
1512               o_fl%flag,o_fl%name, "Denominator of Cloud droplet effective radius"," ")
1513          !FH Sorties pour la couche limite
1514          if (iflag_pbl>1) then
1515             CALL histdef3d(iff,clef_stations(iff), &
1516                  o_tke%flag,o_tke%name, "TKE", "m2/s2")
1517             IF (.NOT.clef_stations(iff)) THEN
1518                !
1519                !IM: there is no way to have one single value in a netcdf file
1520                !
1521                type_ecri(1) = 't_max(X)'
1522                type_ecri(2) = 't_max(X)'
1523                type_ecri(3) = 't_max(X)'
1524                type_ecri(4) = 't_max(X)'
1525                type_ecri(5) = 't_max(X)'
1526                type_ecri(6) = 't_max(X)'
1527                CALL histdef3d(iff,clef_stations(iff), &
1528                     o_tke_max%flag,o_tke_max%name, "TKE max", "m2/s2")
1529             ENDIF
1530             type_ecri(:) = type_ecri_files(:)
1531          endif
1532
1533          CALL histdef3d(iff,clef_stations(iff), &
1534               o_kz%flag,o_kz%name, "Kz melange", "m2/s")
1535          IF (.NOT.clef_stations(iff)) THEN
1536             !
1537             !IM: there is no way to have one single value in a netcdf file
1538             !
1539             type_ecri(1) = 't_max(X)'
1540             type_ecri(2) = 't_max(X)'
1541             type_ecri(3) = 't_max(X)'
1542             type_ecri(4) = 't_max(X)'
1543             type_ecri(5) = 't_max(X)'
1544             type_ecri(6) = 't_max(X)'
1545             CALL histdef3d(iff,clef_stations(iff), &
1546                  o_kz_max%flag,o_kz_max%name, "Kz melange max", "m2/s" )
1547          ENDIF
1548          type_ecri(:) = type_ecri_files(:)
1549          CALL histdef3d(iff,clef_stations(iff), &
1550               o_clwcon%flag,o_clwcon%name, "Convective Cloud Liquid water content", "kg/kg")
1551          CALL histdef3d(iff,clef_stations(iff), &
1552               o_dtdyn%flag,o_dtdyn%name, "Dynamics dT", "K/s")
1553          CALL histdef3d(iff,clef_stations(iff), &
1554               o_dqdyn%flag,o_dqdyn%name, "Dynamics dQ", "(kg/kg)/s")
1555          CALL histdef3d(iff,clef_stations(iff), &
1556               o_dudyn%flag,o_dudyn%name, "Dynamics dU", "m/s2")
1557          CALL histdef3d(iff,clef_stations(iff), &
1558               o_dvdyn%flag,o_dvdyn%name, "Dynamics dV", "m/s2")
1559          CALL histdef3d(iff,clef_stations(iff), &
1560               o_dtcon%flag,o_dtcon%name, "Convection dT", "K/s")
1561          CALL histdef3d(iff,clef_stations(iff), &
1562               o_ducon%flag,o_ducon%name, "Convection du", "m/s2")
1563          CALL histdef3d(iff,clef_stations(iff), &
1564               o_dvcon%flag,o_dvcon%name, "Convection dv", "m/s2")
1565          CALL histdef3d(iff,clef_stations(iff), &
1566               o_dqcon%flag,o_dqcon%name, "Convection dQ", "(kg/kg)/s")
1567
1568          ! Wakes
1569          IF(iflag_con.EQ.3) THEN
1570             IF (iflag_wake >= 1) THEN
1571                CALL histdef2d(iff,clef_stations(iff), &
1572                     o_ale_wk%flag,o_ale_wk%name, "ALE WK", "m2/s2")
1573                CALL histdef2d(iff,clef_stations(iff), &
1574                     o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2")
1575                CALL histdef2d(iff,clef_stations(iff), &
1576                     o_ale%flag,o_ale%name, "ALE", "m2/s2")
1577                CALL histdef2d(iff,clef_stations(iff), &
1578                     o_alp%flag,o_alp%name, "ALP", "W/m2")
1579                CALL histdef2d(iff,clef_stations(iff),o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2")
1580                CALL histdef2d(iff,clef_stations(iff),o_wape%flag,o_WAPE%name, "WAPE", "m2/s2")
1581                CALL histdef2d(iff,clef_stations(iff),o_wake_h%flag,o_wake_h%name, "wake_h", "-")
1582                CALL histdef2d(iff,clef_stations(iff),o_wake_s%flag,o_wake_s%name, "wake_s", "-")
1583                CALL histdef3d(iff,clef_stations(iff),o_dtwak%flag,o_dtwak%name, "Wake dT", "K/s")
1584                CALL histdef3d(iff,clef_stations(iff),o_dqwak%flag,o_dqwak%name, "Wake dQ", "(kg/kg)/s")
1585                CALL histdef3d(iff,clef_stations(iff),o_wake_deltat%flag,o_wake_deltat%name, "wake_deltat", " ")
1586                CALL histdef3d(iff,clef_stations(iff),o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ")
1587                CALL histdef3d(iff,clef_stations(iff),o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ")
1588             ENDIF
1589!!! RomP             CALL histdef3d(iff,clef_stations(iff),o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-")
1590             CALL histdef3d(iff,clef_stations(iff),o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-")
1591             CALL histdef3d(iff,clef_stations(iff),o_fqd%flag,o_fqd%name,"tend vap eau due aux descentes precip", "-")
1592          ENDIF !(iflag_con.EQ.3)
1593
1594          IF(iflag_con.GE.3) THEN   !  RomP >>>
1595            CALL histdef3d(iff,clef_stations(iff),o_wdtrainA%flag,o_wdtrainA%name, "precipitation from AA", "-")
1596            CALL histdef3d(iff,clef_stations(iff),o_wdtrainM%flag,o_wdtrainM%name, "precipitation from mixture", "-")
1597            CALL histdef3d(iff,clef_stations(iff),o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-")
1598          ENDIF !(iflag_con.GE.3)   ! <<< RomP
1599
1600!!! nrlmd le 10/04/2012
1601
1602        IF (iflag_trig_bl>=1) THEN
1603 CALL histdef2d(iff,clef_stations(iff),o_n2%flag,o_n2%name, "Nombre de panaches de type 2", " ")
1604 CALL histdef2d(iff,clef_stations(iff),o_s2%flag,o_s2%name, "Surface moyenne des panaches de type 2", "m2")
1605
1606 CALL histdef2d(iff,clef_stations(iff),o_proba_notrig%flag,o_proba_notrig%name, "Probabilité de non-déclenchement", " ")
1607 CALL histdef2d(iff,clef_stations(iff),o_random_notrig%flag,o_random_notrig%name, "Tirage aléatoire de non-déclenchement", " ")
1608 CALL histdef2d(iff,clef_stations(iff),o_ale_bl_trig%flag,o_ale_bl_trig%name, "ALE_BL_STAT + Condition P>Pseuil", "m2/s2")
1609 CALL histdef2d(iff,clef_stations(iff),o_ale_bl_stat%flag,o_ale_bl_stat%name, "ALE_BL_STAT", "m2/s2")
1610       ENDIF  !(iflag_trig_bl>=1)
1611
1612        IF (iflag_clos_bl>=1) THEN
1613 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_det%flag,o_alp_bl_det%name, "ALP_BL_DET", "W/m2")
1614 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_fluct_m%flag,o_alp_bl_fluct_m%name, "ALP_BL_FLUCT_M", "W/m2")
1615 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_fluct_tke%flag,o_alp_bl_fluct_tke%name, "ALP_BL_FLUCT_TKE", "W/m2")
1616 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_conv%flag,o_alp_bl_conv%name, "ALP_BL_CONV", "W/m2")
1617 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_stat%flag,o_alp_bl_stat%name, "ALP_BL_STAT", "W/m2")
1618       ENDIF  !(iflag_clos_bl>=1)
1619
1620!!! fin nrlmd le 10/04/2012
1621
1622          CALL histdef3d(iff,clef_stations(iff),o_dtlsc%flag,o_dtlsc%name, "Condensation dT", "K/s")
1623          CALL histdef3d(iff,clef_stations(iff),o_dtlschr%flag,o_dtlschr%name,"Large-scale condensational heating rate","K/s")
1624          CALL histdef3d(iff,clef_stations(iff),o_dqlsc%flag,o_dqlsc%name, "Condensation dQ", "(kg/kg)/s")
1625          CALL histdef3d(iff,clef_stations(iff),o_beta_prec%flag,o_beta_prec%name, "LS Conversion rate to prec", "(kg/kg)/s")
1626          CALL histdef3d(iff,clef_stations(iff),o_dtvdf%flag,o_dtvdf%name, "Boundary-layer dT", "K/s")
1627          CALL histdef3d(iff,clef_stations(iff),o_dqvdf%flag,o_dqvdf%name, "Boundary-layer dQ", "(kg/kg)/s")
1628          CALL histdef3d(iff,clef_stations(iff),o_dteva%flag,o_dteva%name, "Reevaporation dT", "K/s")
1629          CALL histdef3d(iff,clef_stations(iff),o_dqeva%flag,o_dqeva%name, "Reevaporation dQ", "(kg/kg)/s")
1630          CALL histdef3d(iff,clef_stations(iff),o_ptconv%flag,o_ptconv%name, "POINTS CONVECTIFS", " ")
1631          CALL histdef3d(iff,clef_stations(iff),o_ratqs%flag,o_ratqs%name, "RATQS", " ")
1632          CALL histdef3d(iff,clef_stations(iff),o_dtthe%flag,o_dtthe%name, "Thermal dT", "K/s")
1633
1634          if(iflag_thermals.ge.1) THEN
1635             CALL histdef3d(iff,clef_stations(iff),o_dqlscth%flag,o_dqlscth%name, "dQ therm.", "(kg/kg)/s")
1636             CALL histdef3d(iff,clef_stations(iff),o_dqlscst%flag,o_dqlscst%name, "dQ strat.", "(kg/kg)/s")
1637             CALL histdef3d(iff,clef_stations(iff),o_dtlscth%flag,o_dtlscth%name, "dQ therm.", "K/s")
1638             CALL histdef3d(iff,clef_stations(iff),o_dtlscst%flag,o_dtlscst%name, "dQ strat.", "K/s")
1639             CALL histdef2d(iff,clef_stations(iff),o_plulth%flag,o_plulth%name, "Rainfall therm.", "K/s")
1640             CALL histdef2d(iff,clef_stations(iff),o_plulst%flag,o_plulst%name, "Rainfall strat.", "K/s")
1641             CALL histdef2d(iff,clef_stations(iff),o_lmaxth%flag,o_lmaxth%name, "Upper level thermals", "")
1642             CALL histdef3d(iff,clef_stations(iff),o_ptconvth%flag,o_ptconvth%name, "POINTS CONVECTIFS therm.", " ")
1643             CALL histdef3d(iff,clef_stations(iff),o_f_th%flag,o_f_th%name, "Thermal plume mass flux", "kg/(m2*s)")
1644             CALL histdef3d(iff,clef_stations(iff),o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s")
1645             CALL histdef3d(iff,clef_stations(iff),o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s")
1646             CALL histdef2d(iff,clef_stations(iff), &
1647                  o_ftime_th%flag,o_ftime_th%name,"Fraction of time Shallow convection occurs"," ")
1648             CALL histdef3d(iff,clef_stations(iff), &
1649                  o_q_th%flag,o_q_th%name, "Thermal plume total humidity", "kg/kg")
1650             CALL histdef3d(iff,clef_stations(iff), &
1651                  o_a_th%flag,o_a_th%name, "Thermal plume fraction", "")
1652             CALL histdef3d(iff,clef_stations(iff), &
1653                  o_d_th%flag,o_d_th%name, "Thermal plume detrainment", "K/s")
1654
1655             CALL histdef2d(iff,clef_stations(iff), &
1656                  o_f0_th%flag,o_f0_th%name, "Thermal closure mass flux", "K/s")
1657             CALL histdef2d(iff,clef_stations(iff), &
1658                  o_zmax_th%flag,o_zmax_th%name, "Thermal plume height", "K/s")
1659             CALL histdef3d(iff,clef_stations(iff), &
1660                  o_dqthe%flag,o_dqthe%name, "Thermal dQ", "(kg/kg)/s")
1661          endif !iflag_thermals.ge.1
1662          CALL histdef3d(iff,clef_stations(iff), &
1663               o_dtajs%flag,o_dtajs%name, "Dry adjust. dT", "K/s")
1664          CALL histdef3d(iff,clef_stations(iff), &
1665               o_dqajs%flag,o_dqajs%name, "Dry adjust. dQ", "(kg/kg)/s")
1666          CALL histdef3d(iff,clef_stations(iff), &
1667               o_dtswr%flag,o_dtswr%name, "SW radiation dT", "K/s")
1668          CALL histdef3d(iff,clef_stations(iff), &
1669               o_dtsw0%flag,o_dtsw0%name, "CS SW radiation dT", "K/s")
1670          CALL histdef3d(iff,clef_stations(iff), &
1671               o_dtlwr%flag,o_dtlwr%name, "LW radiation dT", "K/s")
1672          CALL histdef3d(iff,clef_stations(iff), &
1673               o_dtlw0%flag,o_dtlw0%name, "CS LW radiation dT", "K/s")
1674          CALL histdef3d(iff,clef_stations(iff), &
1675               o_dtec%flag,o_dtec%name, "Cinetic dissip dT", "K/s")
1676          CALL histdef3d(iff,clef_stations(iff), &
1677               o_duvdf%flag,o_duvdf%name, "Boundary-layer dU", "m/s2")
1678          CALL histdef3d(iff,clef_stations(iff), &
1679               o_dvvdf%flag,o_dvvdf%name, "Boundary-layer dV", "m/s2")
1680
1681          IF (ok_orodr) THEN
1682             CALL histdef3d(iff,clef_stations(iff), &
1683                  o_duoro%flag,o_duoro%name, "Orography dU", "m/s2")
1684             CALL histdef3d(iff,clef_stations(iff), &
1685                  o_dvoro%flag,o_dvoro%name, "Orography dV", "m/s2")
1686             CALL histdef3d(iff,clef_stations(iff), &
1687                  o_dtoro%flag,o_dtoro%name, "Orography dT", "K/s")
1688          ENDIF
1689
1690          IF (ok_orolf) THEN
1691             CALL histdef3d(iff,clef_stations(iff), &
1692                  o_dulif%flag,o_dulif%name, "Orography dU", "m/s2")
1693             CALL histdef3d(iff,clef_stations(iff), &
1694                  o_dvlif%flag,o_dvlif%name, "Orography dV", "m/s2")
1695             CALL histdef3d(iff,clef_stations(iff), &
1696                  o_dtlif%flag,o_dtlif%name, "Orography dT", "K/s")
1697          ENDIF
1698
1699          IF (ok_hines) then
1700             CALL histdef3d(iff,clef_stations(iff), &
1701                  o_duhin%flag,o_duhin%name, "Hines GWD dU", "m/s2")
1702             CALL histdef3d(iff,clef_stations(iff), &
1703                  o_dvhin%flag,o_dvhin%name, "Hines GWD dV", "m/s2")
1704
1705             CALL histdef3d(iff,clef_stations(iff), &
1706                  o_dthin%flag,o_dthin%name, "Hines GWD dT", "K/s")
1707          ENDIF
1708
1709          CALL histdef3d(iff,clef_stations(iff), &
1710               o_rsu%flag,o_rsu%name, "SW upward radiation", "W m-2")
1711          CALL histdef3d(iff,clef_stations(iff), &
1712               o_rsd%flag,o_rsd%name, "SW downward radiation", "W m-2")
1713          CALL histdef3d(iff,clef_stations(iff), &
1714               o_rlu%flag,o_rlu%name, "LW upward radiation", "W m-2")
1715          CALL histdef3d(iff,clef_stations(iff), &
1716               o_rld%flag,o_rld%name, "LW downward radiation", "W m-2")
1717
1718          CALL histdef3d(iff,clef_stations(iff), &
1719               o_rsucs%flag,o_rsucs%name, "SW CS upward radiation", "W m-2")
1720          CALL histdef3d(iff,clef_stations(iff), &
1721               o_rsdcs%flag,o_rsdcs%name, "SW CS downward radiation", "W m-2")
1722          CALL histdef3d(iff,clef_stations(iff), &
1723               o_rlucs%flag,o_rlucs%name, "LW CS upward radiation", "W m-2")
1724          CALL histdef3d(iff,clef_stations(iff), &
1725               o_rldcs%flag,o_rldcs%name, "LW CS downward radiation", "W m-2")
1726
1727          CALL histdef3d(iff,clef_stations(iff), &
1728               o_tnt%flag,o_tnt%name, "Tendency of air temperature", "K s-1")
1729
1730          CALL histdef3d(iff,clef_stations(iff), &
1731               o_tntc%flag,o_tntc%name, "Tendency of air temperature due to Moist Convection", &
1732               "K s-1")
1733
1734          CALL histdef3d(iff,clef_stations(iff), &
1735               o_tntr%flag,o_tntr%name, "Air temperature tendency due to Radiative heating", &
1736               "K s-1")
1737
1738          CALL histdef3d(iff,clef_stations(iff), &
1739               o_tntscpbl%flag,o_tntscpbl%name, "Air temperature tendency due to St cloud and precipitation and BL mixing", &
1740               "K s-1")
1741
1742          CALL histdef3d(iff,clef_stations(iff), &
1743               o_tnhus%flag,o_tnhus%name, "Tendency of specific humidity", "s-1")
1744
1745          CALL histdef3d(iff,clef_stations(iff), &
1746               o_tnhusc%flag,o_tnhusc%name, "Tendency of specific humidity due to convection", "s-1")
1747
1748          CALL histdef3d(iff,clef_stations(iff), &
1749               o_tnhusscpbl%flag,o_tnhusscpbl%name, "Tendency of Specific humidity due to ST cl, precip and BL mixing", &
1750               "s-1")
1751
1752          CALL histdef3d(iff,clef_stations(iff), &
1753               o_evu%flag,o_evu%name, "Eddy viscosity coefficient for Momentum Variables", "m2 s-1")
1754
1755          CALL histdef3d(iff,clef_stations(iff), &
1756               o_h2o%flag,o_h2o%name, "Mass Fraction of Water", "1")
1757
1758          CALL histdef3d(iff,clef_stations(iff), &
1759               o_mcd%flag,o_mcd%name, "Downdraft COnvective Mass Flux", "kg/(m2*s)")
1760
1761          CALL histdef3d(iff,clef_stations(iff), &
1762               o_dmc%flag,o_dmc%name, "Deep COnvective Mass Flux", "kg/(m2*s)")
1763
1764          CALL histdef3d(iff,clef_stations(iff), &
1765               o_ref_liq%flag,o_ref_liq%name, "Effective radius of convective cloud liquid water particle", "m")
1766
1767          CALL histdef3d(iff,clef_stations(iff), &
1768               o_ref_ice%flag,o_ref_ice%name, "Effective radius of startiform cloud ice particle", "m")
1769
1770          if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. &
1771               RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR. &
1772               RCFC12_per.NE.RCFC12_act) THEN
1773
1774             CALL histdef2d(iff,clef_stations(iff),o_rsut4co2%flag,o_rsut4co2%name, &
1775                  "TOA Out SW in 4xCO2 atmosphere", "W/m2")
1776             CALL histdef2d(iff,clef_stations(iff),o_rlut4co2%flag,o_rlut4co2%name, &
1777                  "TOA Out LW in 4xCO2 atmosphere", "W/m2")
1778             CALL histdef2d(iff,clef_stations(iff),o_rsutcs4co2%flag,o_rsutcs4co2%name, &
1779                  "TOA Out CS SW in 4xCO2 atmosphere", "W/m2")
1780             CALL histdef2d(iff,clef_stations(iff),o_rlutcs4co2%flag,o_rlutcs4co2%name, &
1781                  "TOA Out CS LW in 4xCO2 atmosphere", "W/m2")
1782
1783             CALL histdef3d(iff,clef_stations(iff),o_rsu4co2%flag,o_rsu4co2%name, &
1784                  "Upwelling SW 4xCO2 atmosphere", "W/m2")
1785             CALL histdef3d(iff,clef_stations(iff),o_rlu4co2%flag,o_rlu4co2%name, &
1786                  "Upwelling LW 4xCO2 atmosphere", "W/m2")
1787             CALL histdef3d(iff,clef_stations(iff),o_rsucs4co2%flag,o_rsucs4co2%name, &
1788                  "Upwelling CS SW 4xCO2 atmosphere", "W/m2")
1789             CALL histdef3d(iff,clef_stations(iff),o_rlucs4co2%flag,o_rlucs4co2%name, &
1790                  "Upwelling CS LW 4xCO2 atmosphere", "W/m2")
1791
1792             CALL histdef3d(iff,clef_stations(iff),o_rsd4co2%flag,o_rsd4co2%name, &
1793                  "Downwelling SW 4xCO2 atmosphere", "W/m2")
1794             CALL histdef3d(iff,clef_stations(iff),o_rld4co2%flag,o_rld4co2%name, &
1795                  "Downwelling LW 4xCO2 atmosphere", "W/m2")
1796             CALL histdef3d(iff,clef_stations(iff),o_rsdcs4co2%flag,o_rsdcs4co2%name, &
1797                  "Downwelling CS SW 4xCO2 atmosphere", "W/m2")
1798             CALL histdef3d(iff,clef_stations(iff),o_rldcs4co2%flag,o_rldcs4co2%name, &
1799                  "Downwelling CS LW 4xCO2 atmosphere", "W/m2")
1800
1801          endif
1802
1803
1804          IF (nqtot>=3) THEN
1805             DO iq=3,nqtot 
1806                iiq=niadv(iq)
1807                o_trac(iq-2) = ctrl_out((/ 4, 5, 1, 1, 1, 10 /),tname(iiq))
1808                CALL histdef3d (iff,clef_stations(iff), &
1809                o_trac(iq-2)%flag,o_trac(iq-2)%name,'Tracer '//ttext(iiq), "-" )
1810                o_trac_cum(iq-2) = ctrl_out((/ 3, 4, 10, 10, 10, 10 /),'cum'//tname(iiq))
1811                CALL histdef2d (iff,clef_stations(iff), &
1812                o_trac_cum(iq-2)%flag,o_trac_cum(iq-2)%name,'Cumulated tracer '//ttext(iiq), "-" )
1813             ENDDO
1814          ENDIF
1815
1816          CALL histend(nid_files(iff))
1817
1818          ndex2d = 0
1819          ndex3d = 0
1820
1821       ENDIF ! clef_files
1822
1823    ENDDO !  iff
1824
1825    ! Updated write frequencies due to phys_out_filetimesteps.
1826    ! Write frequencies are now in seconds. 
1827    ecrit_mth = ecrit_files(1)
1828    ecrit_day = ecrit_files(2)
1829    ecrit_hf  = ecrit_files(3)
1830    ecrit_ins = ecrit_files(4)
1831    ecrit_LES = ecrit_files(5)
1832    ecrit_ins = ecrit_files(6)
1833
1834    write(lunout,*)'swaero_diag=',swaero_diag
1835    write(lunout,*)'Fin phys_output_mod.F90'
1836  end subroutine phys_output_open
1837
1838  SUBROUTINE histdef2d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
1839
1840    use ioipsl
1841    USE dimphy
1842    USE mod_phys_lmdz_para
1843    USE iophy
1844
1845    IMPLICIT NONE
1846
1847    include "dimensions.h"
1848    include "temps.h"
1849    include "indicesol.h"
1850    include "clesphys.h"
1851
1852    integer                          :: iff
1853    logical                          :: lpoint
1854    integer, dimension(nfiles)       :: flag_var
1855    character(len=20)                 :: nomvar
1856    character(len=*)                 :: titrevar
1857    character(len=*)                 :: unitvar
1858
1859    real zstophym
1860
1861    if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
1862       zstophym=zoutm(iff)
1863    else
1864       zstophym=zdtime
1865    endif
1866
1867    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
1868    call conf_physoutputs(nomvar,flag_var)
1869
1870    if(.NOT.lpoint) THEN 
1871       if ( flag_var(iff)<=lev_files(iff) ) then
1872          call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
1873               iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
1874               type_ecri(iff), zstophym,zoutm(iff))               
1875       endif
1876    else
1877       if ( flag_var(iff)<=lev_files(iff) ) then
1878          call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
1879               npstn,1,nhorim(iff), 1,1,1, -99, 32, &
1880               type_ecri(iff), zstophym,zoutm(iff))               
1881       endif
1882    endif
1883
1884    ! Set swaero_diag=true if at least one of the concerned variables are defined
1885    if (nomvar=='topswad' .OR. nomvar=='topswai' .OR. nomvar=='solswad' .OR. nomvar=='solswai' ) THEN
1886       if  ( flag_var(iff)<=lev_files(iff) ) then
1887          swaero_diag=.TRUE.
1888       end if
1889    end if
1890  end subroutine histdef2d
1891
1892  SUBROUTINE histdef3d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)
1893
1894    use ioipsl
1895    USE dimphy
1896    USE mod_phys_lmdz_para
1897    USE iophy
1898
1899    IMPLICIT NONE
1900
1901    include "dimensions.h"
1902    include "temps.h"
1903    include "indicesol.h"
1904    include "clesphys.h"
1905
1906    integer                          :: iff
1907    logical                          :: lpoint
1908    integer, dimension(nfiles)       :: flag_var
1909    character(len=20)                 :: nomvar
1910    character(len=*)                 :: titrevar
1911    character(len=*)                 :: unitvar
1912
1913    real zstophym
1914
1915    ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
1916    call conf_physoutputs(nomvar,flag_var)
1917
1918    if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
1919       zstophym=zoutm(iff)
1920    else
1921       zstophym=zdtime
1922    endif
1923
1924    if(.NOT.lpoint) THEN
1925       if ( flag_var(iff)<=lev_files(iff) ) then
1926          call histdef (nid_files(iff), nomvar, titrevar, unitvar, &
1927               iim, jj_nb, nhorim(iff), klev, levmin(iff), &
1928               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), &
1929               zstophym, zoutm(iff))
1930       endif
1931    else
1932       if ( flag_var(iff)<=lev_files(iff) ) then
1933          call histdef (nid_files(iff), nomvar, titrevar, unitvar, &
1934               npstn,1,nhorim(iff), klev, levmin(iff), &
1935               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, &
1936               type_ecri(iff), zstophym,zoutm(iff))
1937       endif
1938    endif
1939  end subroutine histdef3d
1940
1941  SUBROUTINE conf_physoutputs(nam_var,flag_var)
1942!!! Lecture des noms et niveau de sortie des variables dans output.def
1943    !   en utilisant les routines getin de IOIPSL 
1944    use ioipsl
1945
1946    IMPLICIT NONE
1947
1948    include 'iniprint.h'
1949
1950    character(len=20)                :: nam_var
1951    integer, dimension(nfiles)      :: flag_var
1952
1953    IF(prt_level>10) WRITE(lunout,*)'Avant getin: nam_var flag_var ',nam_var,flag_var(:)
1954    call getin('flag_'//nam_var,flag_var)
1955    call getin('name_'//nam_var,nam_var)
1956    IF(prt_level>10) WRITE(lunout,*)'Apres getin: nam_var flag_var ',nam_var,flag_var(:)
1957
1958  END SUBROUTINE conf_physoutputs
1959
1960  SUBROUTINE convers_timesteps(str,dtime,timestep)
1961
1962    use ioipsl
1963    USE phys_cal_mod
1964
1965    IMPLICIT NONE
1966
1967    character(len=20)   :: str
1968    character(len=10)   :: type
1969    integer             :: ipos,il
1970    real                :: ttt,xxx,timestep,dayseconde,dtime
1971    parameter (dayseconde=86400.)
1972    include "temps.h"
1973    include "comconst.h"
1974    include "iniprint.h"
1975
1976    ipos=scan(str,'0123456789.',.true.)
1977    ! 
1978    il=len_trim(str)
1979    write(lunout,*)ipos,il
1980    read(str(1:ipos),*) ttt
1981    write(lunout,*)ttt
1982    type=str(ipos+1:il)
1983
1984
1985    if ( il == ipos ) then
1986       type='day'
1987    endif
1988
1989    if ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde
1990    if ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then
1991       write(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len
1992       timestep = ttt * dayseconde * mth_len
1993    endif
1994    if ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.
1995    if ( type == 'mn'.or.type == 'minutes'  ) timestep = ttt * 60.
1996    if ( type == 's'.or.type == 'sec'.or.type == 'secondes'   ) timestep = ttt
1997    if ( type == 'TS' ) timestep = ttt * dtime
1998
1999    write(lunout,*)'type =      ',type
2000    write(lunout,*)'nb j/h/m =  ',ttt
2001    write(lunout,*)'timestep(s)=',timestep
2002
2003  END SUBROUTINE convers_timesteps
2004
2005END MODULE phys_output_mod
2006
Note: See TracBrowser for help on using the repository browser.