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

Last change on this file since 1764 was 1764, checked in by Laurent Fairhead, 11 years ago

Inclusion d'une routine qui lit des champs d'aérosols stratosphériques
mensuels, prescrit des propriétés optiques et modifie le rayonnement en
conséquence. Pour le moment, seule l'interaction avec le rayonnement ondes
courtes est pris en compte. Les fichiers d'input doivent être au format des
fichiers de sortie. Contrôlé par la variable logique: flag_aerosol_strat
(false par défaut dans DefLists?/config.def)

  1. Boucher

A new routine has been added to the code that reads in monthly stratospheric
aerosols, prescribes optical properties and modifies radiation accordingly.
Presently, only the interaction with short wave radiation is taken into account.
Input files must be formatted as are the aerosol output fields. Control is by
the logical flag: flag_aerosol_strat (which is false by default and included
DefLists?/config.def)

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