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

Last change on this file since 1562 was 1562, checked in by lguez, 13 years ago

"YOEGWD.h" is now valid and equivalent for either free source form or
fixed source form.

Bug fix in "phys_output_mod.F90" and "phys_output_write.h": we were
potentially averaging undefined values of "plcl", "plfc" and
"wbeff". Added condition:
if (iflag_con /= 30)
for writing those variables.

Indented file "phys_output_mod.F90".

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