source: LMDZ4/branches/LMDZ4_AR5/libf/phylmd/phys_output_mod.F90 @ 1536

Last change on this file since 1536 was 1536, checked in by musat, 13 years ago

Petites corrections pour le cas ou l'on veut pas sortir de fichier
histstn (et qu'on a pas les fichiers initiaux correspondants).
IM

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