source: LMDZ4/trunk/libf/phylmd/phys_output_mod.F90 @ 1375

Last change on this file since 1375 was 1375, checked in by Laurent Fairhead, 14 years ago

Variable output level definition for each file for the CMIP5 exercise:

  • level 5 corresponds to CMIP5 "core" output for all files
  • the level for CFMIP outputs will vary according to the output frequency

of the file (e.g. 6 for the '3-hours' file)
For aerosols, outputs that do not require supplementary computations are
put to 2 for the monthly history file and 6 for the daily one


Définition des niveaux de sorties des variables par fichier pour CMIP5:

  • le niveau 5 correspond aux sorties CMIP5 "core" pour tous les fichiers
  • le niveau pour les sorties CFMIP varie selon la fréquence de sortie

du fichier (6 pour le fichier "3 heures")
Pour les aérosols, les sorties qui n'engendrent pas de calculs supplémentaires
sont passées en 2 pour le fichier mensuel et 6 pour le journalier

SD, ACo

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 79.6 KB
Line 
1! $Id: phys_output_mod.F90 1375 2010-05-05 10:22:05Z fairhead $
2!
3! Abderrahmane 12 2007
4!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
5!!! Ecreture des Sorties du modele dans les fichiers Netcdf :
6! histmth.nc : moyennes mensuelles
7! histday.nc : moyennes journalieres
8! histhf.nc  : moyennes toutes les 3 heures
9! histins.nc : valeurs instantanees
10!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
11
12MODULE phys_output_mod
13
14  IMPLICIT NONE
15
16  private histdef2d, histdef3d, conf_physoutputs
17
18
19   integer, parameter                           :: nfiles = 5
20   logical, dimension(nfiles), save             :: clef_files
21   integer, dimension(nfiles), save             :: lev_files
22   integer, dimension(nfiles), save             :: nid_files
23!!$OMP THREADPRIVATE(clef_files, lev_files,nid_files)
24 
25   integer, dimension(nfiles), private, save :: nhorim, nvertm
26   integer, dimension(nfiles), private, save :: nvertap, nvertbp, nvertAlt
27!   integer, dimension(nfiles), private, save :: nvertp0
28   real, dimension(nfiles), private, save                :: zoutm
29   real,                    private, save                :: zdtime
30   CHARACTER(len=20), dimension(nfiles), private, save   :: type_ecri
31!$OMP THREADPRIVATE(nhorim, nvertm, zoutm,zdtime,type_ecri)
32
33!   integer, save                     :: nid_hf3d
34
35!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
36!! Definition pour chaque variable du niveau d ecriture dans chaque fichier
37!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!/ histmth, histday, histhf, histins /),'!!!!!!!!!!!!
38!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
39
40  integer, private:: levmin(nfiles) = 1
41  integer, private:: levmax(nfiles)
42
43  TYPE ctrl_out
44   integer,dimension(5) :: flag
45   character(len=20)     :: name
46  END TYPE ctrl_out
47
48!!! Comosentes de la coordonnee sigma-hybride
49!!! Ap et Bp
50  type(ctrl_out),save :: o_Ahyb         = ctrl_out((/ 1, 1, 1, 1, 1 /), 'Ap')
51  type(ctrl_out),save :: o_Bhyb         = ctrl_out((/ 1, 1, 1, 1, 1 /), 'Bp')
52  type(ctrl_out),save :: o_Alt          = ctrl_out((/ 1, 1, 1, 1, 1 /), 'Alt')
53
54!!! 1D
55  type(ctrl_out),save :: o_phis         = ctrl_out((/ 1, 1, 10, 5, 1 /), 'phis')
56  type(ctrl_out),save :: o_aire         = ctrl_out((/ 1, 1, 10,  10, 1 /),'aire')
57  type(ctrl_out),save :: o_contfracATM  = ctrl_out((/ 10, 1,  1, 10, 10 /),'contfracATM')
58  type(ctrl_out),save :: o_contfracOR   = ctrl_out((/ 10, 1,  1, 10, 10 /),'contfracOR')
59  type(ctrl_out),save :: o_aireTER      = ctrl_out((/ 10, 10, 1, 10, 10 /),'aireTER')
60 
61!!! 2D
62  type(ctrl_out),save :: o_flat         = ctrl_out((/ 5, 1, 10, 5, 1 /),'flat')
63  type(ctrl_out),save :: o_slp          = ctrl_out((/ 1, 1, 1, 10, 1 /),'slp')
64  type(ctrl_out),save :: o_tsol         = ctrl_out((/ 1, 1, 1, 5, 1 /),'tsol')
65  type(ctrl_out),save :: o_t2m          = ctrl_out((/ 1, 1, 1, 5, 1 /),'t2m')
66  type(ctrl_out),save :: o_t2m_min      = ctrl_out((/ 1, 1, 10, 10, 10 /),'t2m_min')
67  type(ctrl_out),save :: o_t2m_max      = ctrl_out((/ 1, 1, 10, 10, 10 /),'t2m_max')
68  type(ctrl_out),save,dimension(4) :: o_t2m_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'t2m_ter'), &
69                                                 ctrl_out((/ 10, 4, 10, 10, 10 /),'t2m_lic'), &
70                                                 ctrl_out((/ 10, 4, 10, 10, 10 /),'t2m_oce'), &
71                                                 ctrl_out((/ 10, 4, 10, 10, 10 /),'t2m_sic') /)
72
73  type(ctrl_out),save :: o_wind10m      = ctrl_out((/ 1, 1, 1, 10, 10 /),'wind10m')
74  type(ctrl_out),save :: o_wind10max    = ctrl_out((/ 10, 1, 10, 10, 10 /),'wind10max')
75  type(ctrl_out),save :: o_sicf         = ctrl_out((/ 1, 1, 10, 10, 10 /),'sicf')
76  type(ctrl_out),save :: o_q2m          = ctrl_out((/ 1, 1, 1, 5, 1 /),'q2m')
77  type(ctrl_out),save :: o_u10m         = ctrl_out((/ 1, 1, 1, 5, 1 /),'u10m')
78  type(ctrl_out),save :: o_v10m         = ctrl_out((/ 1, 1, 1, 5, 1 /),'v10m')
79  type(ctrl_out),save :: o_psol         = ctrl_out((/ 1, 1, 1, 5, 1 /),'psol')
80  type(ctrl_out),save :: o_qsurf        = ctrl_out((/ 1, 10, 10, 10, 10 /),'qsurf')
81
82  type(ctrl_out),save,dimension(4) :: o_u10m_srf     = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'u10m_ter'), &
83                                              ctrl_out((/ 10, 4, 10, 10, 10 /),'u10m_lic'), &
84                                              ctrl_out((/ 10, 4, 10, 10, 10 /),'u10m_oce'), &
85                                              ctrl_out((/ 10, 4, 10, 10, 10 /),'u10m_sic') /)
86
87  type(ctrl_out),save,dimension(4) :: o_v10m_srf     = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'v10m_ter'), &
88                                              ctrl_out((/ 10, 4, 10, 10, 10 /),'v10m_lic'), &
89                                              ctrl_out((/ 10, 4, 10, 10, 10 /),'v10m_oce'), &
90                                              ctrl_out((/ 10, 4, 10, 10, 10 /),'v10m_sic') /)
91
92  type(ctrl_out),save :: o_qsol         = ctrl_out((/ 1, 10, 10, 10, 10 /),'qsol')
93
94  type(ctrl_out),save :: o_ndayrain     = ctrl_out((/ 1, 10, 10, 10, 10 /),'ndayrain')
95  type(ctrl_out),save :: o_precip       = ctrl_out((/ 1, 1, 1, 5, 10 /),'precip')
96  type(ctrl_out),save :: o_plul         = ctrl_out((/ 1, 1, 1, 10, 10 /),'plul')
97
98  type(ctrl_out),save :: o_pluc         = ctrl_out((/ 1, 1, 1, 5, 10 /),'pluc')
99  type(ctrl_out),save :: o_snow         = ctrl_out((/ 1, 1, 10, 5, 10 /),'snow')
100  type(ctrl_out),save :: o_evap         = ctrl_out((/ 1, 1, 10, 10, 10 /),'evap')
101  type(ctrl_out),save,dimension(4) :: o_evap_srf     = (/ ctrl_out((/ 1, 1, 10, 10, 10 /),'evap_ter'), &
102                                           ctrl_out((/ 1, 1, 10, 10, 10 /),'evap_lic'), &
103                                           ctrl_out((/ 1, 1, 10, 10, 10 /),'evap_oce'), &
104                                           ctrl_out((/ 1, 1, 10, 10, 10 /),'evap_sic') /)
105  type(ctrl_out),save :: o_msnow       = ctrl_out((/ 1, 10, 10, 10, 10 /),'msnow')
106  type(ctrl_out),save :: o_fsnow       = ctrl_out((/ 1, 10, 10, 10, 10 /),'fsnow')
107
108  type(ctrl_out),save :: o_tops         = ctrl_out((/ 1, 1, 10, 10, 10 /),'tops')
109  type(ctrl_out),save :: o_tops0        = ctrl_out((/ 1, 5, 10, 10, 10 /),'tops0')
110  type(ctrl_out),save :: o_topl         = ctrl_out((/ 1, 1, 10, 5, 10 /),'topl')
111  type(ctrl_out),save :: o_topl0        = ctrl_out((/ 1, 5, 10, 10, 10 /),'topl0')
112  type(ctrl_out),save :: o_SWupTOA      = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWupTOA')
113  type(ctrl_out),save :: o_SWupTOAclr   = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWupTOAclr')
114  type(ctrl_out),save :: o_SWdnTOA      = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWdnTOA')
115  type(ctrl_out),save :: o_SWdnTOAclr   = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWdnTOAclr')
116  type(ctrl_out),save :: o_nettop       = ctrl_out((/ 1, 4, 10, 10, 10 /),'nettop')
117
118  type(ctrl_out),save :: o_SWup200      = ctrl_out((/ 1, 10, 10, 10, 10 /),'SWup200')
119  type(ctrl_out),save :: o_SWup200clr   = ctrl_out((/ 10, 1, 10, 10, 10 /),'SWup200clr')
120  type(ctrl_out),save :: o_SWdn200      = ctrl_out((/ 1, 10, 10, 10, 10 /),'SWdn200')
121  type(ctrl_out),save :: o_SWdn200clr   = ctrl_out((/ 10, 1, 10, 10, 10 /),'SWdn200clr')
122
123! arajouter
124!  type(ctrl_out),save :: o_LWupTOA     = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWupTOA')
125!  type(ctrl_out),save :: o_LWupTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWupTOAclr')
126!  type(ctrl_out),save :: o_LWdnTOA     = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWdnTOA')
127!  type(ctrl_out),save :: o_LWdnTOAclr  = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWdnTOAclr')
128
129  type(ctrl_out),save :: o_LWup200      = ctrl_out((/ 1, 10, 10, 10, 10 /),'LWup200')
130  type(ctrl_out),save :: o_LWup200clr   = ctrl_out((/ 1, 10, 10, 10, 10 /),'LWup200clr')
131  type(ctrl_out),save :: o_LWdn200      = ctrl_out((/ 1, 10, 10, 10, 10 /),'LWdn200')
132  type(ctrl_out),save :: o_LWdn200clr   = ctrl_out((/ 1, 10, 10, 10, 10 /),'LWdn200clr')
133  type(ctrl_out),save :: o_sols         = ctrl_out((/ 1, 1, 10, 10, 10 /),'sols')
134  type(ctrl_out),save :: o_sols0        = ctrl_out((/ 1, 5, 10, 10, 10 /),'sols0')
135  type(ctrl_out),save :: o_soll         = ctrl_out((/ 1, 1, 10, 10, 10 /),'soll')
136  type(ctrl_out),save :: o_soll0        = ctrl_out((/ 1, 5, 10, 10, 10 /),'soll0')
137  type(ctrl_out),save :: o_radsol       = ctrl_out((/ 1, 1, 10, 10, 10 /),'radsol')
138  type(ctrl_out),save :: o_SWupSFC      = ctrl_out((/ 1, 4, 10, 5, 10 /),'SWupSFC')
139  type(ctrl_out),save :: o_SWupSFCclr   = ctrl_out((/ 1, 4, 10, 10, 10 /),'SWupSFCclr')
140  type(ctrl_out),save :: o_SWdnSFC      = ctrl_out((/ 1, 1, 10, 5, 10 /),'SWdnSFC')
141  type(ctrl_out),save :: o_SWdnSFCclr   = ctrl_out((/ 1, 4, 10, 5, 10 /),'SWdnSFCclr')
142  type(ctrl_out),save :: o_LWupSFC      = ctrl_out((/ 1, 4, 10, 10, 10 /),'LWupSFC')
143  type(ctrl_out),save :: o_LWupSFCclr   = ctrl_out((/ 1, 4, 10, 5, 10 /),'LWupSFCclr')
144  type(ctrl_out),save :: o_LWdnSFC      = ctrl_out((/ 1, 4, 10, 5, 10 /),'LWdnSFC')
145  type(ctrl_out),save :: o_LWdnSFCclr   = ctrl_out((/ 1, 4, 10, 5, 10 /),'LWdnSFCclr')
146  type(ctrl_out),save :: o_bils         = ctrl_out((/ 1, 2, 10, 5, 10 /),'bils')
147  type(ctrl_out),save :: o_sens         = ctrl_out((/ 1, 1, 10, 5, 10 /),'sens')
148  type(ctrl_out),save :: o_fder         = ctrl_out((/ 1, 2, 10, 10, 10 /),'fder')
149  type(ctrl_out),save :: o_ffonte       = ctrl_out((/ 1, 10, 10, 10, 10 /),'ffonte')
150  type(ctrl_out),save :: o_fqcalving    = ctrl_out((/ 1, 10, 10, 10, 10 /),'fqcalving')
151  type(ctrl_out),save :: o_fqfonte      = ctrl_out((/ 1, 10, 10, 10, 10 /),'fqfonte')
152
153  type(ctrl_out),save :: o_taux         = ctrl_out((/ 1, 10, 10, 10, 10 /),'taux')
154  type(ctrl_out),save :: o_tauy         = ctrl_out((/ 1, 10, 10, 10, 10 /),'tauy')
155  type(ctrl_out),save,dimension(4) :: o_taux_srf     = (/ ctrl_out((/ 1, 4, 10, 10, 10 /),'taux_ter'), &
156                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'taux_lic'), &
157                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'taux_oce'), &
158                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'taux_sic') /)
159
160  type(ctrl_out),save,dimension(4) :: o_tauy_srf     = (/ ctrl_out((/ 1, 4, 10, 10, 10 /),'tauy_ter'), &
161                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'tauy_lic'), &
162                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'tauy_oce'), &
163                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'tauy_sic') /)
164
165
166  type(ctrl_out),save,dimension(4) :: o_pourc_srf    = (/ ctrl_out((/ 1, 4, 10, 10, 10 /),'pourc_ter'), &
167                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'pourc_lic'), &
168                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'pourc_oce'), &
169                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'pourc_sic') /)     
170
171  type(ctrl_out),save,dimension(4) :: o_fract_srf    = (/ ctrl_out((/ 1, 4, 10, 10, 10 /),'fract_ter'), &
172                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'fract_lic'), &
173                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'fract_oce'), &
174                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'fract_sic') /)
175
176  type(ctrl_out),save,dimension(4) :: o_tsol_srf     = (/ ctrl_out((/ 1, 4, 10, 10, 10 /),'tsol_ter'), &
177                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'tsol_lic'), &
178                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'tsol_oce'), &
179                                                 ctrl_out((/ 1, 4, 10, 10, 10 /),'tsol_sic') /)
180
181  type(ctrl_out),save,dimension(4) :: o_sens_srf     = (/ ctrl_out((/ 1, 4, 10, 1, 10 /),'sens_ter'), &
182                                                 ctrl_out((/ 1, 4, 10, 1, 10 /),'sens_lic'), &
183                                                 ctrl_out((/ 1, 4, 10, 1, 10 /),'sens_oce'), &
184                                                 ctrl_out((/ 1, 4, 10, 1, 10 /),'sens_sic') /)
185
186  type(ctrl_out),save,dimension(4) :: o_lat_srf      = (/ ctrl_out((/ 1, 4, 10, 1, 10 /),'lat_ter'), &
187                                                 ctrl_out((/ 1, 4, 10, 1, 10 /),'lat_lic'), &
188                                                 ctrl_out((/ 1, 4, 10, 1, 10 /),'lat_oce'), &
189                                                 ctrl_out((/ 1, 4, 10, 1, 10 /),'lat_sic') /)
190
191  type(ctrl_out),save,dimension(4) :: o_flw_srf      = (/ ctrl_out((/ 1, 10, 10, 10, 10 /),'flw_ter'), &
192                                                 ctrl_out((/ 1, 10, 10, 10, 10 /),'flw_lic'), &
193                                                 ctrl_out((/ 1, 10, 10, 10, 10 /),'flw_oce'), &
194                                                 ctrl_out((/ 1, 10, 10, 10, 10 /),'flw_sic') /)
195                                                 
196  type(ctrl_out),save,dimension(4) :: o_fsw_srf      = (/ ctrl_out((/ 1, 10, 10, 10, 10 /),'fsw_ter'), &
197                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'fsw_lic'), &
198                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'fsw_oce'), &
199                                                  ctrl_out((/ 1, 10, 10, 10, 10 /),'fsw_sic') /)
200
201  type(ctrl_out),save,dimension(4) :: o_wbils_srf    = (/ ctrl_out((/ 1, 10, 10, 10, 10 /),'wbils_ter'), &
202                                                 ctrl_out((/ 1, 10, 10, 10, 10 /),'wbils_lic'), &
203                                                 ctrl_out((/ 1, 10, 10, 10, 10 /),'wbils_oce'), &
204                                                 ctrl_out((/ 1, 10, 10, 10, 10 /),'wbils_sic') /)
205
206  type(ctrl_out),save,dimension(4) :: o_wbilo_srf    = (/ ctrl_out((/ 1, 10, 10, 10, 10 /),'wbilo_ter'), &
207                                                     ctrl_out((/ 1, 10, 10, 10, 10 /),'wbilo_lic'), &
208                                                 ctrl_out((/ 1, 10, 10, 10, 10 /),'wbilo_oce'), &
209                                                 ctrl_out((/ 1, 10, 10, 10, 10 /),'wbilo_sic') /)
210
211
212  type(ctrl_out),save :: o_cdrm         = ctrl_out((/ 1, 10, 10, 10, 10 /),'cdrm')
213  type(ctrl_out),save :: o_cdrh         = ctrl_out((/ 1, 10, 10, 1, 10 /),'cdrh')
214  type(ctrl_out),save :: o_cldl         = ctrl_out((/ 1, 1, 10, 10, 10 /),'cldl')
215  type(ctrl_out),save :: o_cldm         = ctrl_out((/ 1, 1, 10, 10, 10 /),'cldm')
216  type(ctrl_out),save :: o_cldh         = ctrl_out((/ 1, 1, 10, 10, 10 /),'cldh')
217  type(ctrl_out),save :: o_cldt         = ctrl_out((/ 1, 1, 2, 5, 10 /),'cldt')
218  type(ctrl_out),save :: o_cldq         = ctrl_out((/ 1, 1, 10, 10, 10 /),'cldq')
219  type(ctrl_out),save :: o_lwp          = ctrl_out((/ 1, 5, 10, 10, 10 /),'lwp')
220  type(ctrl_out),save :: o_iwp          = ctrl_out((/ 1, 5, 10, 10, 10 /),'iwp')
221  type(ctrl_out),save :: o_ue           = ctrl_out((/ 1, 10, 10, 10, 10 /),'ue')
222  type(ctrl_out),save :: o_ve           = ctrl_out((/ 1, 10, 10, 10, 10 /),'ve')
223  type(ctrl_out),save :: o_uq           = ctrl_out((/ 1, 10, 10, 10, 10 /),'uq')
224  type(ctrl_out),save :: o_vq           = ctrl_out((/ 1, 10, 10, 10, 10 /),'vq')
225 
226  type(ctrl_out),save :: o_cape         = ctrl_out((/ 1, 10, 10, 10, 10 /),'cape')
227  type(ctrl_out),save :: o_pbase        = ctrl_out((/ 1, 5, 10, 10, 10 /),'pbase')
228  type(ctrl_out),save :: o_ptop         = ctrl_out((/ 1, 5, 10, 10, 10 /),'ptop')
229  type(ctrl_out),save :: o_fbase        = ctrl_out((/ 1, 10, 10, 10, 10 /),'fbase')
230  type(ctrl_out),save :: o_prw          = ctrl_out((/ 1, 1, 10, 10, 10 /),'prw')
231
232  type(ctrl_out),save :: o_s_pblh       = ctrl_out((/ 1, 10, 10, 10, 1 /),'s_pblh')
233  type(ctrl_out),save :: o_s_pblt       = ctrl_out((/ 1, 10, 10, 10, 1 /),'s_pblt')
234  type(ctrl_out),save :: o_s_lcl        = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_lcl')
235  type(ctrl_out),save :: o_s_capCL      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_capCL')
236  type(ctrl_out),save :: o_s_oliqCL     = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_oliqCL')
237  type(ctrl_out),save :: o_s_cteiCL     = ctrl_out((/ 1, 10, 10, 10, 1 /),'s_cteiCL')
238  type(ctrl_out),save :: o_s_therm      = ctrl_out((/ 1, 10, 10, 10, 1 /),'s_therm')
239  type(ctrl_out),save :: o_s_trmb1      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_trmb1')
240  type(ctrl_out),save :: o_s_trmb2      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_trmb2')
241  type(ctrl_out),save :: o_s_trmb3      = ctrl_out((/ 1, 10, 10, 10, 10 /),'s_trmb3')
242
243  type(ctrl_out),save :: o_slab_bils    = ctrl_out((/ 1, 1, 10, 10, 10 /),'slab_bils_oce')
244
245  type(ctrl_out),save :: o_ale_bl       = ctrl_out((/ 1, 1, 1, 10, 10 /),'ale_bl')
246  type(ctrl_out),save :: o_alp_bl       = ctrl_out((/ 1, 1, 1, 10, 10 /),'alp_bl')
247  type(ctrl_out),save :: o_ale_wk       = ctrl_out((/ 1, 1, 1, 10, 10 /),'ale_wk')
248  type(ctrl_out),save :: o_alp_wk       = ctrl_out((/ 1, 1, 1, 10, 10 /),'alp_wk')
249
250  type(ctrl_out),save :: o_ale          = ctrl_out((/ 1, 1, 1, 10, 10 /),'ale')
251  type(ctrl_out),save :: o_alp          = ctrl_out((/ 1, 1, 1, 10, 10 /),'alp')
252  type(ctrl_out),save :: o_cin          = ctrl_out((/ 1, 1, 1, 10, 10 /),'cin')
253  type(ctrl_out),save :: o_wape         = ctrl_out((/ 1, 1, 1, 10, 10 /),'wape')
254
255
256! Champs interpolles sur des niveaux de pression ??? a faire correctement
257                                             
258  type(ctrl_out),save,dimension(6) :: o_uSTDlevs     = (/ ctrl_out((/ 1, 1, 3, 10, 10 /),'u850'), &
259                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'u700'), &
260                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'u500'), &
261                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'u200'), &
262                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'u50'), &
263                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'u10') /)
264                                                     
265
266  type(ctrl_out),save,dimension(6) :: o_vSTDlevs     = (/ ctrl_out((/ 1, 1, 3, 10, 10 /),'v850'), &
267                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'v700'), &
268                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'v500'), &
269                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'v200'), &
270                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'v50'), &
271                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'v10') /)
272
273  type(ctrl_out),save,dimension(6) :: o_wSTDlevs     = (/ ctrl_out((/ 1, 1, 3, 10, 10 /),'w850'), &
274                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'w700'), &
275                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'w500'), &
276                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'w200'), &
277                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'w50'), &
278                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'w10') /)
279
280  type(ctrl_out),save,dimension(6) :: o_tSTDlevs     = (/ ctrl_out((/ 1, 1, 3, 10, 10 /),'t850'), &
281                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'t700'), &
282                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'t500'), &
283                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'t200'), &
284                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'t50'), &
285                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'t10') /)
286
287  type(ctrl_out),save,dimension(6) :: o_qSTDlevs     = (/ ctrl_out((/ 1, 1, 3, 10, 10 /),'q850'), &
288                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'q700'), &
289                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'q500'), &
290                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'q200'), &
291                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'q50'), &
292                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'q10') /)
293
294  type(ctrl_out),save,dimension(6) :: o_phiSTDlevs   = (/ ctrl_out((/ 1, 1, 3, 10, 10 /),'phi850'), &
295                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'phi700'), &
296                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'phi500'), &
297                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'phi200'), &
298                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'phi50'), &
299                                                     ctrl_out((/ 1, 1, 3, 10, 10 /),'phi10') /)
300
301
302  type(ctrl_out),save :: o_t_oce_sic    = ctrl_out((/ 1, 10, 10, 10, 10 /),'t_oce_sic')
303
304  type(ctrl_out),save :: o_weakinv      = ctrl_out((/ 10, 1, 10, 10, 10 /),'weakinv')
305  type(ctrl_out),save :: o_dthmin       = ctrl_out((/ 10, 1, 10, 10, 10 /),'dthmin')
306  type(ctrl_out),save,dimension(4) :: o_u10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'u10_ter'), &
307                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'u10_lic'), &
308                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'u10_oce'), &
309                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'u10_sic') /)
310
311  type(ctrl_out),save,dimension(4) :: o_v10_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'v10_ter'), &
312                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'v10_lic'), &
313                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'v10_oce'), &
314                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'v10_sic') /)
315
316  type(ctrl_out),save :: o_cldtau       = ctrl_out((/ 10, 5, 10, 10, 10 /),'cldtau')                     
317  type(ctrl_out),save :: o_cldemi       = ctrl_out((/ 10, 5, 10, 10, 10 /),'cldemi')
318  type(ctrl_out),save :: o_rh2m         = ctrl_out((/ 5, 5, 10, 10, 10 /),'rh2m')
319  type(ctrl_out),save :: o_rh2m_min     = ctrl_out((/ 10, 5, 10, 10, 10 /),'rh2m_min')
320  type(ctrl_out),save :: o_rh2m_max     = ctrl_out((/ 10, 5, 10, 10, 10 /),'rh2m_max')
321  type(ctrl_out),save :: o_qsat2m       = ctrl_out((/ 10, 5, 10, 10, 10 /),'qsat2m')
322  type(ctrl_out),save :: o_tpot         = ctrl_out((/ 10, 5, 10, 10, 10 /),'tpot')
323  type(ctrl_out),save :: o_tpote        = ctrl_out((/ 10, 5, 10, 10, 10 /),'tpote')
324  type(ctrl_out),save :: o_tke          = ctrl_out((/ 4, 10, 10, 10, 10 /),'tke ')
325  type(ctrl_out),save :: o_tke_max      = ctrl_out((/ 4, 10, 10, 10, 10 /),'tke_max')
326
327  type(ctrl_out),save,dimension(4) :: o_tke_srf      = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_ter'), &
328                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_lic'), &
329                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_oce'), &
330                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_sic') /)
331
332  type(ctrl_out),save,dimension(4) :: o_tke_max_srf  = (/ ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_max_ter'), &
333                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_max_lic'), &
334                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_max_oce'), &
335                                                     ctrl_out((/ 10, 4, 10, 10, 10 /),'tke_max_sic') /)
336
337  type(ctrl_out),save :: o_kz           = ctrl_out((/ 4, 10, 10, 10, 10 /),'kz')
338  type(ctrl_out),save :: o_kz_max       = ctrl_out((/ 4, 10, 10, 10, 10 /),'kz_max')
339  type(ctrl_out),save :: o_SWnetOR      = ctrl_out((/ 10, 10, 2, 10, 10 /),'SWnetOR')
340  type(ctrl_out),save :: o_SWdownOR     = ctrl_out((/ 10, 10, 2, 10, 10 /),'SWdownOR')
341  type(ctrl_out),save :: o_LWdownOR     = ctrl_out((/ 10, 10, 2, 10, 10 /),'LWdownOR')
342
343  type(ctrl_out),save :: o_snowl        = ctrl_out((/ 10, 1, 10, 10, 10 /),'snowl')
344  type(ctrl_out),save :: o_cape_max     = ctrl_out((/ 10, 1, 10, 10, 10 /),'cape_max')
345  type(ctrl_out),save :: o_solldown     = ctrl_out((/ 10, 1, 10, 10, 10 /),'solldown')
346
347  type(ctrl_out),save :: o_dtsvdfo      = ctrl_out((/ 10, 10, 10, 10, 10 /),'dtsvdfo')
348  type(ctrl_out),save :: o_dtsvdft      = ctrl_out((/ 10, 10, 10, 10, 10 /),'dtsvdft')
349  type(ctrl_out),save :: o_dtsvdfg      = ctrl_out((/ 10, 10, 10, 10, 10 /),'dtsvdfg')
350  type(ctrl_out),save :: o_dtsvdfi      = ctrl_out((/ 10, 10, 10, 10, 10 /),'dtsvdfi')
351  type(ctrl_out),save :: o_rugs         = ctrl_out((/ 10, 10, 10, 10, 10 /),'rugs')
352
353  type(ctrl_out),save :: o_topswad      = ctrl_out((/ 2, 10, 10, 10, 10 /),'topswad')
354  type(ctrl_out),save :: o_topswai      = ctrl_out((/ 2, 10, 10, 10, 10 /),'topswai')
355  type(ctrl_out),save :: o_solswad      = ctrl_out((/ 2, 10, 10, 10, 10 /),'solswad')
356  type(ctrl_out),save :: o_solswai      = ctrl_out((/ 2, 10, 10, 10, 10 /),'solswai')
357
358  type(ctrl_out),save,dimension(10) :: o_tausumaero  = (/ ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_ASBCM'), &
359                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_ASPOMM'), &
360                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_ASSO4M'), &
361                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_CSSO4M'), &
362                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_SSSSM'), &
363                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_ASSSM'), &
364                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_CSSSM'), &
365                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_CIDUSTM'), &
366                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_AIBCM'), &
367                                                     ctrl_out((/ 2, 6, 10, 10, 10 /),'OD550_AIPOMM') /)
368
369  type(ctrl_out),save :: o_od550aer     = ctrl_out((/ 2, 6, 10, 10, 10 /),'od550aer')
370  type(ctrl_out),save :: o_od865aer     = ctrl_out((/ 2, 6, 10, 10, 10 /),'od865aer')
371  type(ctrl_out),save :: o_absvisaer    = ctrl_out((/ 2, 6, 10, 10, 10 /),'absvisaer')
372  type(ctrl_out),save :: o_od550lt1aer  = ctrl_out((/ 2, 6, 10, 10, 10 /),'od550lt1aer')
373
374  type(ctrl_out),save :: o_sconcso4     = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcso4')
375  type(ctrl_out),save :: o_sconcoa      = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcoa')
376  type(ctrl_out),save :: o_sconcbc      = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcbc')
377  type(ctrl_out),save :: o_sconcss      = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcss')
378  type(ctrl_out),save :: o_sconcdust    = ctrl_out((/ 2, 6, 10, 10, 10 /),'sconcdust')
379  type(ctrl_out),save :: o_concso4      = ctrl_out((/ 2, 6, 10, 10, 10 /),'concso4')
380  type(ctrl_out),save :: o_concoa       = ctrl_out((/ 2, 6, 10, 10, 10 /),'concoa')
381  type(ctrl_out),save :: o_concbc       = ctrl_out((/ 2, 6, 10, 10, 10 /),'concbc')
382  type(ctrl_out),save :: o_concss       = ctrl_out((/ 2, 6, 10, 10, 10 /),'concss')
383  type(ctrl_out),save :: o_concdust     = ctrl_out((/ 2, 6, 10, 10, 10 /),'concdust')
384  type(ctrl_out),save :: o_loadso4      = ctrl_out((/ 2, 6, 10, 10, 10 /),'loadso4')
385  type(ctrl_out),save :: o_loadoa       = ctrl_out((/ 2, 6, 10, 10, 10 /),'loadoa')
386  type(ctrl_out),save :: o_loadbc       = ctrl_out((/ 2, 6, 10, 10, 10 /),'loadbc')
387  type(ctrl_out),save :: o_loadss       = ctrl_out((/ 2, 6, 10, 10, 10 /),'loadss')
388  type(ctrl_out),save :: o_loaddust     = ctrl_out((/ 2, 6, 10, 10, 10 /),'loaddust')
389
390  type(ctrl_out),save :: o_swtoaas_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoaas_nat')
391  type(ctrl_out),save :: o_swsrfas_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfas_nat')
392  type(ctrl_out),save :: o_swtoacs_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacs_nat')
393  type(ctrl_out),save :: o_swsrfcs_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcs_nat')
394
395  type(ctrl_out),save :: o_swtoaas_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoaas_ant')
396  type(ctrl_out),save :: o_swsrfas_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfas_ant')
397  type(ctrl_out),save :: o_swtoacs_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacs_ant')
398  type(ctrl_out),save :: o_swsrfcs_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcs_ant')
399
400  type(ctrl_out),save :: o_swtoacf_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacf_nat')
401  type(ctrl_out),save :: o_swsrfcf_nat  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcf_nat')
402  type(ctrl_out),save :: o_swtoacf_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacf_ant')
403  type(ctrl_out),save :: o_swsrfcf_ant  = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcf_ant')
404  type(ctrl_out),save :: o_swtoacf_zero = ctrl_out((/ 4, 6, 10, 10, 10 /),'swtoacf_zero')
405  type(ctrl_out),save :: o_swsrfcf_zero = ctrl_out((/ 4, 6, 10, 10, 10 /),'swsrfcf_zero')
406
407  type(ctrl_out),save :: o_cldncl       = ctrl_out((/ 2, 6, 10, 10, 10 /),'cldncl')
408  type(ctrl_out),save :: o_reffclwtop   = ctrl_out((/ 2, 6, 10, 10, 10 /),'reffclwtop')
409  type(ctrl_out),save :: o_cldnvi       = ctrl_out((/ 2, 6, 10, 10, 10 /),'cldnvi')
410  type(ctrl_out),save :: o_lcc          = ctrl_out((/ 2, 6, 10, 10, 10 /),'lcc')
411
412
413!!!!!!!!!!!!!!!!!!!!!! 3D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
414  type(ctrl_out),save :: o_ec550aer     = ctrl_out((/ 2, 6, 10, 10, 1 /),'ec550aer')
415  type(ctrl_out),save :: o_lwcon        = ctrl_out((/ 2, 5, 10, 10, 1 /),'lwcon')
416  type(ctrl_out),save :: o_iwcon        = ctrl_out((/ 2, 5, 10, 10, 10 /),'iwcon')
417  type(ctrl_out),save :: o_temp         = ctrl_out((/ 2, 3, 4, 10, 1 /),'temp')
418  type(ctrl_out),save :: o_theta        = ctrl_out((/ 2, 3, 4, 10, 1 /),'theta')
419  type(ctrl_out),save :: o_ovap         = ctrl_out((/ 2, 3, 4, 10, 1 /),'ovap')
420  type(ctrl_out),save :: o_ovapinit     = ctrl_out((/ 2, 3, 10, 10, 1 /),'ovapinit')
421  type(ctrl_out),save :: o_wvapp        = ctrl_out((/ 2, 10, 10, 10, 10 /),'wvapp')
422  type(ctrl_out),save :: o_geop         = ctrl_out((/ 2, 3, 10, 10, 1 /),'geop')
423  type(ctrl_out),save :: o_vitu         = ctrl_out((/ 2, 3, 4, 6, 1 /),'vitu')
424  type(ctrl_out),save :: o_vitv         = ctrl_out((/ 2, 3, 4, 6, 1 /),'vitv')
425  type(ctrl_out),save :: o_vitw         = ctrl_out((/ 2, 3, 10, 6, 1 /),'vitw')
426  type(ctrl_out),save :: o_pres         = ctrl_out((/ 2, 3, 10, 10, 1 /),'pres')
427  type(ctrl_out),save :: o_paprs        = ctrl_out((/ 2, 3, 10, 10, 1 /),'paprs')
428  type(ctrl_out),save :: o_rneb         = ctrl_out((/ 2, 5, 10, 10, 1 /),'rneb')
429  type(ctrl_out),save :: o_rnebcon      = ctrl_out((/ 2, 5, 10, 10, 1 /),'rnebcon')
430  type(ctrl_out),save :: o_rhum         = ctrl_out((/ 2, 5, 10, 10, 10 /),'rhum')
431  type(ctrl_out),save :: o_ozone        = ctrl_out((/ 2, 10, 10, 10, 10 /),'ozone')
432  type(ctrl_out),save :: o_ozone_light  = ctrl_out((/ 2, 10, 10, 10, 10 /),'ozone_daylight')
433  type(ctrl_out),save :: o_upwd         = ctrl_out((/ 2, 10, 10, 10, 10 /),'upwd')
434  type(ctrl_out),save :: o_dtphy        = ctrl_out((/ 2, 10, 10, 10, 1 /),'dtphy')
435  type(ctrl_out),save :: o_dqphy        = ctrl_out((/ 2, 10, 10, 10, 1 /),'dqphy')
436  type(ctrl_out),save :: o_pr_con_l     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_con_l')
437  type(ctrl_out),save :: o_pr_con_i     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_con_i')
438  type(ctrl_out),save :: o_pr_lsc_l     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_lsc_l')
439  type(ctrl_out),save :: o_pr_lsc_i     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_lsc_i')
440  type(ctrl_out),save :: o_re           = ctrl_out((/ 5, 10, 10, 10, 10 /),'re')
441  type(ctrl_out),save :: o_fl           = ctrl_out((/ 5, 10, 10, 10, 10 /),'fl')
442  type(ctrl_out),save :: o_scdnc        = ctrl_out((/ 2,  6, 10, 10, 1 /),'scdnc')
443  type(ctrl_out),save :: o_reffclws     = ctrl_out((/ 2,  6, 10, 10, 1 /),'reffclws')
444  type(ctrl_out),save :: o_reffclwc     = ctrl_out((/ 2,  6, 10, 10, 1 /),'reffclwc')
445  type(ctrl_out),save :: o_lcc3d        = ctrl_out((/ 2,  6, 10, 10, 1 /),'lcc3d')
446  type(ctrl_out),save :: o_lcc3dcon     = ctrl_out((/ 2,  6, 10, 10, 1 /),'lcc3dcon')
447  type(ctrl_out),save :: o_lcc3dstra    = ctrl_out((/ 2,  6, 10, 10, 1 /),'lcc3dstra')
448!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
449
450  type(ctrl_out),save,dimension(4) :: o_albe_srf     = (/ ctrl_out((/ 3, 4, 10, 1, 10 /),'albe_ter'), &
451                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'albe_lic'), &
452                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'albe_oce'), &
453                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'albe_sic') /)
454
455  type(ctrl_out),save,dimension(4) :: o_ages_srf     = (/ ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_ter'), &
456                                                     ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_lic'), &
457                                                     ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_oce'), &
458                                                     ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_sic') /)
459
460  type(ctrl_out),save,dimension(4) :: o_rugs_srf     = (/ ctrl_out((/ 3, 4, 10, 10, 10 /),'rugs_ter'), &
461                                                     ctrl_out((/ 3, 4, 10, 10, 10 /),'rugs_lic'), &
462                                                     ctrl_out((/ 3, 4, 10, 10, 10 /),'rugs_oce'), &
463                                                     ctrl_out((/ 3, 4, 10, 10, 10 /),'rugs_sic') /)
464
465  type(ctrl_out),save :: o_albs         = ctrl_out((/ 3, 10, 10, 10, 10 /),'albs')
466  type(ctrl_out),save :: o_albslw       = ctrl_out((/ 3, 10, 10, 10, 10 /),'albslw')
467
468  type(ctrl_out),save :: o_clwcon       = ctrl_out((/ 4, 10, 10, 10, 10 /),'clwcon')
469  type(ctrl_out),save :: o_Ma           = ctrl_out((/ 4, 10, 10, 10, 10 /),'Ma')
470  type(ctrl_out),save :: o_dnwd         = ctrl_out((/ 4, 10, 10, 10, 10 /),'dnwd')
471  type(ctrl_out),save :: o_dnwd0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dnwd0')
472  type(ctrl_out),save :: o_mc           = ctrl_out((/ 4, 5, 10, 10, 10 /),'mc')
473  type(ctrl_out),save :: o_ftime_con    = ctrl_out((/ 4, 10, 10, 10, 10 /),'ftime_con')
474  type(ctrl_out),save :: o_dtdyn        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dtdyn')
475  type(ctrl_out),save :: o_dqdyn        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dqdyn')
476  type(ctrl_out),save :: o_dudyn        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dudyn')  !AXC
477  type(ctrl_out),save :: o_dvdyn        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dvdyn')  !AXC
478  type(ctrl_out),save :: o_dtcon        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dtcon')
479  type(ctrl_out),save :: o_ducon        = ctrl_out((/ 4, 10, 10, 10, 10 /),'ducon')
480  type(ctrl_out),save :: o_dqcon        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dqcon')
481  type(ctrl_out),save :: o_dtwak        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dtwak')
482  type(ctrl_out),save :: o_dqwak        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dqwak')
483  type(ctrl_out),save :: o_wake_h       = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_h')
484  type(ctrl_out),save :: o_wake_s       = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_s')
485  type(ctrl_out),save :: o_wake_deltat  = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_deltat')
486  type(ctrl_out),save :: o_wake_deltaq  = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_deltaq')
487  type(ctrl_out),save :: o_wake_omg     = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_omg')
488  type(ctrl_out),save :: o_Vprecip      = ctrl_out((/ 10, 10, 10, 10, 10 /),'Vprecip')
489  type(ctrl_out),save :: o_ftd          = ctrl_out((/ 4, 5, 10, 10, 10 /),'ftd')
490  type(ctrl_out),save :: o_fqd          = ctrl_out((/ 4, 5, 10, 10, 10 /),'fqd')
491  type(ctrl_out),save :: o_dtlsc        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlsc')
492  type(ctrl_out),save :: o_dtlschr      = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlschr')
493  type(ctrl_out),save :: o_dqlsc        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqlsc')
494  type(ctrl_out),save :: o_dtvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtvdf')
495  type(ctrl_out),save :: o_dqvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqvdf')
496  type(ctrl_out),save :: o_dteva        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dteva')
497  type(ctrl_out),save :: o_dqeva        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqeva')
498  type(ctrl_out),save :: o_ptconv       = ctrl_out((/ 4, 10, 10, 10, 10 /),'ptconv')
499  type(ctrl_out),save :: o_ratqs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'ratqs')
500  type(ctrl_out),save :: o_dtthe        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtthe')
501  type(ctrl_out),save :: o_f_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'f_th')
502  type(ctrl_out),save :: o_e_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'e_th')
503  type(ctrl_out),save :: o_w_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'w_th')
504  type(ctrl_out),save :: o_lambda_th    = ctrl_out((/ 10, 10, 10, 10, 10 /),'lambda_th')
505  type(ctrl_out),save :: o_ftime_th     = ctrl_out((/ 10, 10, 10, 10, 10 /),'ftime_th')
506  type(ctrl_out),save :: o_q_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'q_th')
507  type(ctrl_out),save :: o_a_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'a_th')
508  type(ctrl_out),save :: o_d_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'d_th')
509  type(ctrl_out),save :: o_f0_th        = ctrl_out((/ 4, 10, 10, 10, 10 /),'f0_th')
510  type(ctrl_out),save :: o_zmax_th      = ctrl_out((/ 4, 10, 10, 10, 10 /),'zmax_th')
511  type(ctrl_out),save :: o_dqthe        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dqthe')
512  type(ctrl_out),save :: o_dtajs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtajs')
513  type(ctrl_out),save :: o_dqajs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqajs')
514  type(ctrl_out),save :: o_dtswr        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dtswr')
515  type(ctrl_out),save :: o_dtsw0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtsw0')
516  type(ctrl_out),save :: o_dtlwr        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dtlwr')
517  type(ctrl_out),save :: o_dtlw0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlw0')
518  type(ctrl_out),save :: o_dtec         = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtec')
519  type(ctrl_out),save :: o_duvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'duvdf')
520  type(ctrl_out),save :: o_dvvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvvdf')
521  type(ctrl_out),save :: o_duoro        = ctrl_out((/ 4, 10, 10, 10, 10 /),'duoro')
522  type(ctrl_out),save :: o_dvoro        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvoro')
523  type(ctrl_out),save :: o_dulif        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dulif')
524  type(ctrl_out),save :: o_dvlif        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvlif')
525
526! Attention a refaire correctement
527  type(ctrl_out),save,dimension(2) :: o_trac         = (/ ctrl_out((/ 4, 10, 10, 10, 10 /),'trac01'), &
528                                                     ctrl_out((/ 4, 10, 10, 10, 10 /),'trac02') /)
529    CONTAINS
530
531!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
532!!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!!
533!! histbeg, histvert et histdef
534!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
535 
536  SUBROUTINE phys_output_open(jjmp1,nlevSTD,clevSTD,nbteta, &
537       ctetaSTD,dtime, ok_veget, &
538       type_ocean, iflag_pbl,ok_mensuel,ok_journe, &
539       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
540       new_aod, aerosol_couple)   
541
542
543  USE iophy
544  USE dimphy
545  USE infotrac
546  USE ioipsl
547  USE mod_phys_lmdz_para
548  USE aero_mod, only : naero_spc,name_aero
549
550  IMPLICIT NONE
551  include "dimensions.h"
552  include "temps.h"
553  include "indicesol.h"
554  include "clesphys.h"
555  include "thermcell.h"
556  include "comvert.h"
557
558  integer                               :: jjmp1
559  integer                               :: nbteta, nlevSTD, radpas
560  logical                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
561  logical                               :: ok_LES,ok_ade,ok_aie
562  logical                               :: new_aod, aerosol_couple
563  integer, intent(in)::  read_climoz ! read ozone climatology
564  !     Allowed values are 0, 1 and 2
565  !     0: do not read an ozone climatology
566  !     1: read a single ozone climatology that will be used day and night
567  !     2: read two ozone climatologies, the average day and night
568  !     climatology and the daylight climatology
569
570  real                                  :: dtime
571  integer                               :: idayref
572  real                                  :: zjulian
573  real, dimension(klev)                 :: Ahyb, Bhyb, Alt
574  character(len=4), dimension(nlevSTD)  :: clevSTD
575  integer                               :: nsrf, k, iq, iiq, iff, i, j, ilev
576  integer                               :: naero
577  logical                               :: ok_veget
578  integer                               :: iflag_pbl
579  CHARACTER(len=4)                      :: bb2
580  CHARACTER(len=2)                      :: bb3
581  character(len=6)                      :: type_ocean
582  CHARACTER(len=3)                      :: ctetaSTD(nbteta)
583  real, dimension(nfiles)               :: ecrit_files
584  CHARACTER(len=20), dimension(nfiles)  :: phys_out_filenames
585  INTEGER, dimension(iim*jjmp1)         ::  ndex2d
586  INTEGER, dimension(iim*jjmp1*klev)    :: ndex3d
587  integer                               :: imin_ins, imax_ins
588  integer                               :: jmin_ins, jmax_ins
589  integer, dimension(nfiles)            :: phys_out_levmin, phys_out_levmax
590  integer, dimension(nfiles)            :: phys_out_filelevels
591  CHARACTER(len=20), dimension(nfiles)  :: type_ecri_files, phys_out_filetypes
592  character(len=20), dimension(nfiles)  :: chtimestep   = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq' /)
593  logical, dimension(nfiles)            :: phys_out_filekeys
594
595!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
596!                 entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax]
597
598  logical, dimension(nfiles), save  :: phys_out_regfkey       = (/ .false., .false., .false., .false., .false. /)
599  real, dimension(nfiles), save     :: phys_out_lonmin        = (/ -180., -180., -180., -180., -180. /)
600  real, dimension(nfiles), save     :: phys_out_lonmax        = (/ 180., 180., 180., 180., 180. /)
601  real, dimension(nfiles), save     :: phys_out_latmin        = (/ -90., -90., -90., -90., -90. /)
602  real, dimension(nfiles), save     :: phys_out_latmax        = (/ 90., 90., 90., 90., 90. /)
603 
604 
605
606!
607   print*,'Debut phys_output_mod.F90'
608! Initialisations (Valeurs par defaut
609   levmax = (/ klev, klev, klev, klev, klev /)
610
611   phys_out_filenames(1) = 'histmth'
612   phys_out_filenames(2) = 'histday'
613   phys_out_filenames(3) = 'histhf'
614   phys_out_filenames(4) = 'histins'
615   phys_out_filenames(5) = 'histLES'
616
617   type_ecri(1) = 'ave(X)'
618   type_ecri(2) = 'ave(X)'
619   type_ecri(3) = 'ave(X)'
620   type_ecri(4) = 'inst(X)'
621   type_ecri(5) = 'inst(X)'
622
623   clef_files(1) = ok_mensuel
624   clef_files(2) = ok_journe
625   clef_files(3) = ok_hf
626   clef_files(4) = ok_instan
627   clef_files(5) = ok_LES
628
629   lev_files(1) = lev_histmth
630   lev_files(2) = lev_histday
631   lev_files(3) = lev_histhf
632   lev_files(4) = lev_histins
633   lev_files(5) = lev_histLES
634
635
636   ecrit_files(1) = ecrit_mth
637   ecrit_files(2) = ecrit_day
638   ecrit_files(3) = ecrit_hf
639   ecrit_files(4) = ecrit_ins
640   ecrit_files(5) = ecrit_LES
641 
642!! Lectures des parametres de sorties dans physiq.def
643
644   call getin('phys_out_regfkey',phys_out_regfkey)
645   call getin('phys_out_lonmin',phys_out_lonmin)
646   call getin('phys_out_lonmax',phys_out_lonmax)
647   call getin('phys_out_latmin',phys_out_latmin)
648   call getin('phys_out_latmax',phys_out_latmax)
649     phys_out_levmin(:)=levmin(:)
650   call getin('phys_out_levmin',levmin)
651     phys_out_levmax(:)=levmax(:)
652   call getin('phys_out_levmax',levmax)
653   call getin('phys_out_filenames',phys_out_filenames)
654     phys_out_filekeys(:)=clef_files(:)
655   call getin('phys_out_filekeys',clef_files)
656     phys_out_filelevels(:)=lev_files(:)
657   call getin('phys_out_filelevels',lev_files)
658   call getin('phys_out_filetimesteps',chtimestep)
659     phys_out_filetypes(:)=type_ecri(:)
660   call getin('phys_out_filetypes',type_ecri)
661
662   type_ecri_files(:)=type_ecri(:)
663
664   print*,'phys_out_lonmin=',phys_out_lonmin
665   print*,'phys_out_lonmax=',phys_out_lonmax
666   print*,'phys_out_latmin=',phys_out_latmin
667   print*,'phys_out_latmax=',phys_out_latmax
668   print*,'phys_out_filenames=',phys_out_filenames
669   print*,'phys_out_filetypes=',type_ecri
670   print*,'phys_out_filekeys=',clef_files
671   print*,'phys_out_filelevels=',lev_files
672
673!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
674! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
675! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
676!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
677
678 zdtime = dtime         ! Frequence ou l on moyenne
679
680! Calcul des Ahyb, Bhyb et Alt
681         do k=1,klev
682          Ahyb(k)=(ap(k)+ap(k+1))/2.
683          Bhyb(k)=(bp(k)+bp(k+1))/2.
684          Alt(k)=log(preff/presnivs(k))*8.
685         enddo
686!          if(prt_level.ge.1) then
687           print*,'Ap Hybrid = ',Ahyb(1:klev)
688           print*,'Bp Hybrid = ',Bhyb(1:klev)
689           print*,'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)
690!          endif
691 DO iff=1,nfiles
692
693    IF (clef_files(iff)) THEN
694
695      if ( chtimestep(iff).eq.'DefFreq' ) then
696! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf ...)*86400.
697        ecrit_files(iff)=ecrit_files(iff)*86400.
698      else
699        call convers_timesteps(chtimestep(iff),ecrit_files(iff))
700      endif
701       print*,'ecrit_files(',iff,')= ',ecrit_files(iff)
702
703      zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
704
705      idayref = day_ref
706      CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
707
708!!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
709!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
710     if (phys_out_regfkey(iff)) then
711
712        imin_ins=1
713        imax_ins=iim
714        jmin_ins=1
715        jmax_ins=jjmp1
716
717! correction abderr       
718        do i=1,iim
719           print*,'io_lon(i)=',io_lon(i)
720           if (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i
721           if (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1
722        enddo
723
724        do j=1,jjmp1
725            print*,'io_lat(j)=',io_lat(j)
726            if (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1
727            if (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j
728        enddo
729
730        print*,'On stoke le fichier histoire numero ',iff,' sur ', &
731         imin_ins,imax_ins,jmin_ins,jmax_ins
732         print*,'longitudes : ', &
733         io_lon(imin_ins),io_lon(imax_ins), &
734         'latitudes : ', &
735         io_lat(jmax_ins),io_lat(jmin_ins)
736
737 CALL histbeg(phys_out_filenames(iff),iim,io_lon,jjmp1,io_lat, &
738              imin_ins,imax_ins-imin_ins+1, &
739              jmin_ins,jmax_ins-jmin_ins+1, &
740              itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
741!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
742       else
743 CALL histbeg_phy(phys_out_filenames(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
744       endif
745 
746      CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "mb", &
747           levmax(iff) - levmin(iff) + 1, &
748           presnivs(levmin(iff):levmax(iff))/100., nvertm(iff))
749
750!!!!!!!!!!!!! Traitement des champs 3D pour histhf !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
751!!!!!!!!!!!!!!! A Revoir plus tard !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
752!          IF (iff.eq.3.and.lev_files(iff).ge.4) THEN
753!          CALL histbeg_phy("histhf3d",itau_phy, &
754!     &                     zjulian, dtime, &
755!     &                     nhorim, nid_hf3d)
756
757!         CALL histvert(nid_hf3d, "presnivs", &
758!     &                 "Vertical levels", "mb", &
759!     &                 klev, presnivs/100., nvertm)
760!          ENDIF
761!
762!!!! Composentes de la coordonnee sigma-hybride
763   CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
764                 levmax(iff) - levmin(iff) + 1,Ahyb,nvertap(iff))
765
766   CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
767                 levmax(iff) - levmin(iff) + 1,Bhyb,nvertbp(iff))
768
769   CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &
770                 levmax(iff) - levmin(iff) + 1,Alt,nvertAlt(iff))
771
772!   CALL histvert(nid_files(iff), "preff","Reference pressure", "Pa", &
773!                 1,preff,nvertp0(iff))
774!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
775 CALL histdef2d(iff,o_phis%flag,o_phis%name,"Surface geop.height", "m2/s2")
776   type_ecri(1) = 'once'
777   type_ecri(2) = 'once'
778   type_ecri(3) = 'once'
779   type_ecri(4) = 'once'
780   type_ecri(5) = 'once'
781 CALL histdef2d(iff,o_aire%flag,o_aire%name,"Grid area", "-")
782 CALL histdef2d(iff,o_contfracATM%flag,o_contfracATM%name,"% sfce ter+lic", "-")
783   type_ecri(:) = type_ecri_files(:)
784
785!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
786 CALL histdef2d(iff,o_contfracOR%flag,o_contfracOR%name,"% sfce terre OR", "-" )
787 CALL histdef2d(iff,o_aireTER%flag,o_aireTER%name,"Grid area CONT", "-" )
788 CALL histdef2d(iff,o_flat%flag,o_flat%name, "Latent heat flux", "W/m2")
789 CALL histdef2d(iff,o_slp%flag,o_slp%name, "Sea Level Pressure", "Pa" )
790 CALL histdef2d(iff,o_tsol%flag,o_tsol%name, "Surface Temperature", "K")
791 CALL histdef2d(iff,o_t2m%flag,o_t2m%name, "Temperature 2m", "K" )
792   type_ecri(1) = 't_min(X)'
793   type_ecri(2) = 't_min(X)'
794   type_ecri(3) = 't_min(X)'
795   type_ecri(4) = 't_min(X)'
796   type_ecri(5) = 't_min(X)'
797 CALL histdef2d(iff,o_t2m_min%flag,o_t2m_min%name, "Temp 2m min", "K" )
798   type_ecri(1) = 't_max(X)'
799   type_ecri(2) = 't_max(X)'
800   type_ecri(3) = 't_max(X)'
801   type_ecri(4) = 't_max(X)'
802   type_ecri(5) = 't_max(X)'
803 CALL histdef2d(iff,o_t2m_max%flag,o_t2m_max%name, "Temp 2m max", "K" )
804   type_ecri(:) = type_ecri_files(:)
805 CALL histdef2d(iff,o_wind10m%flag,o_wind10m%name, "10-m wind speed", "m/s")
806 CALL histdef2d(iff,o_wind10max%flag,o_wind10max%name, "10m wind speed max", "m/s")
807 CALL histdef2d(iff,o_sicf%flag,o_sicf%name, "Sea-ice fraction", "-" )
808 CALL histdef2d(iff,o_q2m%flag,o_q2m%name, "Specific humidity 2m", "kg/kg")
809 CALL histdef2d(iff,o_u10m%flag,o_u10m%name, "Vent zonal 10m", "m/s" )
810 CALL histdef2d(iff,o_v10m%flag,o_v10m%name, "Vent meridien 10m", "m/s")
811 CALL histdef2d(iff,o_psol%flag,o_psol%name, "Surface Pressure", "Pa" )
812 CALL histdef2d(iff,o_qsurf%flag,o_qsurf%name, "Surface Air humidity", "kg/kg")
813
814  if (.not. ok_veget) then
815 CALL histdef2d(iff,o_qsol%flag,o_qsol%name, "Soil watter content", "mm" )
816  endif
817
818 CALL histdef2d(iff,o_ndayrain%flag,o_ndayrain%name, "Number of dayrain(liq+sol)", "-")
819 CALL histdef2d(iff,o_precip%flag,o_precip%name, "Precip Totale liq+sol", "kg/(s*m2)" )
820 CALL histdef2d(iff,o_plul%flag,o_plul%name, "Large-scale Precip.", "kg/(s*m2)")
821 CALL histdef2d(iff,o_pluc%flag,o_pluc%name, "Convective Precip.", "kg/(s*m2)")
822 CALL histdef2d(iff,o_snow%flag,o_snow%name, "Snow fall", "kg/(s*m2)" )
823 CALL histdef2d(iff,o_msnow%flag,o_msnow%name, "Surface snow amount", "kg/m2" )
824 CALL histdef2d(iff,o_fsnow%flag,o_fsnow%name, "Surface snow area fraction", "-" )
825 CALL histdef2d(iff,o_evap%flag,o_evap%name, "Evaporat", "kg/(s*m2)" )
826 CALL histdef2d(iff,o_tops%flag,o_tops%name, "Solar rad. at TOA", "W/m2")
827 CALL histdef2d(iff,o_tops0%flag,o_tops0%name, "CS Solar rad. at TOA", "W/m2")
828 CALL histdef2d(iff,o_topl%flag,o_topl%name, "IR rad. at TOA", "W/m2" )
829 CALL histdef2d(iff,o_topl0%flag,o_topl0%name, "IR rad. at TOA", "W/m2")
830 CALL histdef2d(iff,o_SWupTOA%flag,o_SWupTOA%name, "SWup at TOA", "W/m2")
831 CALL histdef2d(iff,o_SWupTOAclr%flag,o_SWupTOAclr%name, "SWup clear sky at TOA", "W/m2")
832 CALL histdef2d(iff,o_SWdnTOA%flag,o_SWdnTOA%name, "SWdn at TOA", "W/m2" )
833 CALL histdef2d(iff,o_SWdnTOAclr%flag,o_SWdnTOAclr%name, "SWdn clear sky at TOA", "W/m2")
834 CALL histdef2d(iff,o_nettop%flag,o_nettop%name, "Net dn radiatif flux at TOA", "W/m2")
835 CALL histdef2d(iff,o_SWup200%flag,o_SWup200%name, "SWup at 200mb", "W/m2" )
836 CALL histdef2d(iff,o_SWup200clr%flag,o_SWup200clr%name, "SWup clear sky at 200mb", "W/m2")
837 CALL histdef2d(iff,o_SWdn200%flag,o_SWdn200%name, "SWdn at 200mb", "W/m2" )
838 CALL histdef2d(iff,o_SWdn200clr%flag,o_SWdn200clr%name, "SWdn clear sky at 200mb", "W/m2")
839 CALL histdef2d(iff,o_LWup200%flag,o_LWup200%name, "LWup at 200mb", "W/m2")
840 CALL histdef2d(iff,o_LWup200clr%flag,o_LWup200clr%name, "LWup clear sky at 200mb", "W/m2")
841 CALL histdef2d(iff,o_LWdn200%flag,o_LWdn200%name, "LWdn at 200mb", "W/m2")
842 CALL histdef2d(iff,o_LWdn200clr%flag,o_LWdn200clr%name, "LWdn clear sky at 200mb", "W/m2")
843 CALL histdef2d(iff,o_sols%flag,o_sols%name, "Solar rad. at surf.", "W/m2")
844 CALL histdef2d(iff,o_sols0%flag,o_sols0%name, "Solar rad. at surf.", "W/m2")
845 CALL histdef2d(iff,o_soll%flag,o_soll%name, "IR rad. at surface", "W/m2") 
846 CALL histdef2d(iff,o_radsol%flag,o_radsol%name, "Rayonnement au sol", "W/m2")
847 CALL histdef2d(iff,o_soll0%flag,o_soll0%name, "IR rad. at surface", "W/m2")
848 CALL histdef2d(iff,o_SWupSFC%flag,o_SWupSFC%name, "SWup at surface", "W/m2")
849 CALL histdef2d(iff,o_SWupSFCclr%flag,o_SWupSFCclr%name, "SWup clear sky at surface", "W/m2")
850 CALL histdef2d(iff,o_SWdnSFC%flag,o_SWdnSFC%name, "SWdn at surface", "W/m2")
851 CALL histdef2d(iff,o_SWdnSFCclr%flag,o_SWdnSFCclr%name, "SWdn clear sky at surface", "W/m2")
852 CALL histdef2d(iff,o_LWupSFC%flag,o_LWupSFC%name, "Upwd. IR rad. at surface", "W/m2")
853 CALL histdef2d(iff,o_LWdnSFC%flag,o_LWdnSFC%name, "Down. IR rad. at surface", "W/m2")
854 CALL histdef2d(iff,o_LWupSFCclr%flag,o_LWupSFCclr%name, "CS Upwd. IR rad. at surface", "W/m2")
855 CALL histdef2d(iff,o_LWdnSFCclr%flag,o_LWdnSFCclr%name, "Down. CS IR rad. at surface", "W/m2")
856 CALL histdef2d(iff,o_bils%flag,o_bils%name, "Surf. total heat flux", "W/m2")
857 CALL histdef2d(iff,o_sens%flag,o_sens%name, "Sensible heat flux", "W/m2")
858 CALL histdef2d(iff,o_fder%flag,o_fder%name, "Heat flux derivation", "W/m2")
859 CALL histdef2d(iff,o_ffonte%flag,o_ffonte%name, "Thermal flux for snow melting", "W/m2")
860 CALL histdef2d(iff,o_fqcalving%flag,o_fqcalving%name, "Ice Calving", "kg/m2/s")
861 CALL histdef2d(iff,o_fqfonte%flag,o_fqfonte%name, "Land ice melt", "kg/m2/s")
862
863 CALL histdef2d(iff,o_taux%flag,o_taux%name, "Zonal wind stress","Pa")
864 CALL histdef2d(iff,o_tauy%flag,o_tauy%name, "Meridional wind stress","Pa")
865
866     DO nsrf = 1, nbsrf
867 CALL histdef2d(iff,o_pourc_srf(nsrf)%flag,o_pourc_srf(nsrf)%name,"% "//clnsurf(nsrf),"%")
868 CALL histdef2d(iff,o_fract_srf(nsrf)%flag,o_fract_srf(nsrf)%name,"Fraction "//clnsurf(nsrf),"1")
869 CALL histdef2d(iff,o_taux_srf(nsrf)%flag,o_taux_srf(nsrf)%name,"Zonal wind stress"//clnsurf(nsrf),"Pa")
870 CALL histdef2d(iff,o_tauy_srf(nsrf)%flag,o_tauy_srf(nsrf)%name,"Meridional wind stress "//clnsurf(nsrf),"Pa")
871 CALL histdef2d(iff,o_tsol_srf(nsrf)%flag,o_tsol_srf(nsrf)%name,"Temperature "//clnsurf(nsrf),"K")
872 CALL histdef2d(iff,o_u10m_srf(nsrf)%flag,o_u10m_srf(nsrf)%name,"Vent Zonal 10m "//clnsurf(nsrf),"m/s")
873 CALL histdef2d(iff,o_evap_srf(nsrf)%flag,o_evap_srf(nsrf)%name,"evaporation at surface "//clnsurf(nsrf),"kg/(s*m2)")
874 CALL histdef2d(iff,o_v10m_srf(nsrf)%flag,o_v10m_srf(nsrf)%name,"Vent meredien 10m "//clnsurf(nsrf),"m/s")
875 CALL histdef2d(iff,o_t2m_srf(nsrf)%flag,o_t2m_srf(nsrf)%name,"Temp 2m "//clnsurf(nsrf),"K")
876 CALL histdef2d(iff,o_sens_srf(nsrf)%flag,o_sens_srf(nsrf)%name,"Sensible heat flux "//clnsurf(nsrf),"W/m2")
877 CALL histdef2d(iff,o_lat_srf(nsrf)%flag,o_lat_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
878 CALL histdef2d(iff,o_flw_srf(nsrf)%flag,o_flw_srf(nsrf)%name,"LW "//clnsurf(nsrf),"W/m2")
879 CALL histdef2d(iff,o_fsw_srf(nsrf)%flag,o_fsw_srf(nsrf)%name,"SW "//clnsurf(nsrf),"W/m2")
880 CALL histdef2d(iff,o_wbils_srf(nsrf)%flag,o_wbils_srf(nsrf)%name,"Bilan sol "//clnsurf(nsrf),"W/m2" )
881 CALL histdef2d(iff,o_wbilo_srf(nsrf)%flag,o_wbilo_srf(nsrf)%name,"Bilan eau "//clnsurf(nsrf),"kg/(m2*s)")
882  if (iflag_pbl>1 .and. lev_files(iff).gt.10 ) then
883 CALL histdef2d(iff,o_tke_srf(nsrf)%flag,o_tke_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
884   type_ecri(1) = 't_max(X)'
885   type_ecri(2) = 't_max(X)'
886   type_ecri(3) = 't_max(X)'
887   type_ecri(4) = 't_max(X)'
888   type_ecri(5) = 't_max(X)'
889 CALL histdef2d(iff,o_tke_max_srf(nsrf)%flag,o_tke_max_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
890   type_ecri(:) = type_ecri_files(:)
891  endif
892 CALL histdef2d(iff,o_albe_srf(nsrf)%flag,o_albe_srf(nsrf)%name,"Albedo surf. "//clnsurf(nsrf),"-")
893 CALL histdef2d(iff,o_rugs_srf(nsrf)%flag,o_rugs_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
894 CALL histdef2d(iff,o_ages_srf(nsrf)%flag,o_ages_srf(nsrf)%name,"Snow age", "day")
895END DO
896
897IF (new_aod .AND. (.NOT. aerosol_couple)) THEN
898
899  CALL histdef2d(iff,o_od550aer%flag,o_od550aer%name, "Total aerosol optical depth at 550nm", "-")
900  CALL histdef2d(iff,o_od865aer%flag,o_od865aer%name, "Total aerosol optical depth at 870nm", "-")
901  CALL histdef2d(iff,o_absvisaer%flag,o_absvisaer%name, "Absorption aerosol visible optical depth", "-")
902  CALL histdef2d(iff,o_od550lt1aer%flag,o_od550lt1aer%name, "Fine mode optical depth", "-")
903
904
905  CALL histdef2d(iff,o_sconcso4%flag,o_sconcso4%name,"Surface Concentration of Sulfate ","kg/m3")
906  CALL histdef2d(iff,o_sconcoa%flag,o_sconcoa%name,"Surface Concentration of Organic Aerosol ","kg/m3")
907  CALL histdef2d(iff,o_sconcbc%flag,o_sconcbc%name,"Surface Concentration of Black Carbon ","kg/m3")
908  CALL histdef2d(iff,o_sconcss%flag,o_sconcss%name,"Surface Concentration of Sea Salt ","kg/m3")
909  CALL histdef2d(iff,o_sconcdust%flag,o_sconcdust%name,"Surface Concentration of Dust ","kg/m3")
910  CALL histdef3d(iff,o_concso4%flag,o_concso4%name,"Concentration of Sulfate ","kg/m3")
911  CALL histdef3d(iff,o_concoa%flag,o_concoa%name,"Concentration of Organic Aerosol ","kg/m3")
912  CALL histdef3d(iff,o_concbc%flag,o_concbc%name,"Concentration of Black Carbon ","kg/m3")
913  CALL histdef3d(iff,o_concss%flag,o_concss%name,"Concentration of Sea Salt ","kg/m3")
914  CALL histdef3d(iff,o_concdust%flag,o_concdust%name,"Concentration of Dust ","kg/m3")
915  CALL histdef2d(iff,o_loadso4%flag,o_loadso4%name,"Column Load of Sulfate ","kg/m2")
916  CALL histdef2d(iff,o_loadoa%flag,o_loadoa%name,"Column Load of Organic Aerosol ","kg/m2")
917  CALL histdef2d(iff,o_loadbc%flag,o_loadbc%name,"Column Load of Black Carbon ","kg/m2")
918  CALL histdef2d(iff,o_loadss%flag,o_loadss%name,"Column Load of Sea Salt ","kg/m2")
919  CALL histdef2d(iff,o_loaddust%flag,o_loaddust%name,"Column Load of Dust ","kg/m2")
920
921  DO naero = 1, naero_spc
922  CALL histdef2d(iff,o_tausumaero(naero)%flag,o_tausumaero(naero)%name,"Aerosol Optical depth at 550 nm "//name_aero(naero),"1")
923  END DO
924ENDIF
925
926 IF (ok_ade) THEN
927  CALL histdef2d(iff,o_topswad%flag,o_topswad%name, "ADE at TOA", "W/m2")
928  CALL histdef2d(iff,o_solswad%flag,o_solswad%name, "ADE at SRF", "W/m2")
929
930 CALL histdef2d(iff,o_swtoaas_nat%flag,o_swtoaas_nat%name, "Natural aerosol radiative forcing all-sky at TOA", "W/m2")
931 CALL histdef2d(iff,o_swsrfas_nat%flag,o_swsrfas_nat%name, "Natural aerosol radiative forcing all-sky at SRF", "W/m2")
932 CALL histdef2d(iff,o_swtoacs_nat%flag,o_swtoacs_nat%name, "Natural aerosol radiative forcing clear-sky at TOA", "W/m2")
933 CALL histdef2d(iff,o_swsrfcs_nat%flag,o_swsrfcs_nat%name, "Natural aerosol radiative forcing clear-sky at SRF", "W/m2")
934
935 CALL histdef2d(iff,o_swtoaas_ant%flag,o_swtoaas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at TOA", "W/m2")
936 CALL histdef2d(iff,o_swsrfas_ant%flag,o_swsrfas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at SRF", "W/m2")
937 CALL histdef2d(iff,o_swtoacs_ant%flag,o_swtoacs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at TOA", "W/m2")
938 CALL histdef2d(iff,o_swsrfcs_ant%flag,o_swsrfcs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at SRF", "W/m2")
939
940 IF (.NOT. aerosol_couple) THEN
941 CALL histdef2d(iff,o_swtoacf_nat%flag,o_swtoacf_nat%name, "Natural aerosol impact on cloud radiative forcing at TOA", "W/m2")
942 CALL histdef2d(iff,o_swsrfcf_nat%flag,o_swsrfcf_nat%name, "Natural aerosol impact on cloud radiative forcing  at SRF", "W/m2")
943 CALL histdef2d(iff,o_swtoacf_ant%flag,o_swtoacf_ant%name, "Anthropogenic aerosol impact on cloud radiative forcing at TOA", "W/m2")
944 CALL histdef2d(iff,o_swsrfcf_ant%flag,o_swsrfcf_ant%name, "Anthropogenic aerosol impact on cloud radiative forcing at SRF", "W/m2")
945 CALL histdef2d(iff,o_swtoacf_zero%flag,o_swtoacf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at TOA", "W/m2")
946 CALL histdef2d(iff,o_swsrfcf_zero%flag,o_swsrfcf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at SRF", "W/m2")
947 ENDIF
948
949 ENDIF
950
951 IF (ok_aie) THEN
952  CALL histdef2d(iff,o_topswai%flag,o_topswai%name, "AIE at TOA", "W/m2")
953  CALL histdef2d(iff,o_solswai%flag,o_solswai%name, "AIE at SFR", "W/m2")
954!Cloud droplet number concentration
955  CALL histdef3d(iff,o_scdnc%flag,o_scdnc%name, "Cloud droplet number concentration","m-3")
956  CALL histdef2d(iff,o_cldncl%flag,o_cldncl%name, "CDNC at top of liquid water cloud", "m-3")
957  CALL histdef3d(iff,o_reffclws%flag,o_reffclws%name, "Stratiform Cloud Droplet Effective Radius","m")
958  CALL histdef3d(iff,o_reffclwc%flag,o_reffclwc%name, "Convective Cloud Droplet Effective Radius","m")
959  CALL histdef2d(iff,o_cldnvi%flag,o_cldnvi%name, "Column Integrated Cloud Droplet Number", "m-2")
960  CALL histdef3d(iff,o_lcc3d%flag,o_lcc3d%name, "Cloud liquid fraction","1")
961  CALL histdef3d(iff,o_lcc3dcon%flag,o_lcc3dcon%name, "Convective cloud liquid fraction","1")
962  CALL histdef3d(iff,o_lcc3dstra%flag,o_lcc3dstra%name, "Stratiform cloud liquid fraction","1")
963  CALL histdef2d(iff,o_lcc%flag,o_lcc%name, "Cloud liquid fraction at top of cloud","1")
964  CALL histdef2d(iff,o_reffclwtop%flag,o_reffclwtop%name, "Droplet effective radius at top of liquid water cloud", "m")
965 ENDIF
966
967
968 CALL histdef2d(iff,o_albs%flag,o_albs%name, "Surface albedo", "-")
969 CALL histdef2d(iff,o_albslw%flag,o_albslw%name, "Surface albedo LW", "-")
970 CALL histdef2d(iff,o_cdrm%flag,o_cdrm%name, "Momentum drag coef.", "-")
971 CALL histdef2d(iff,o_cdrh%flag,o_cdrh%name, "Heat drag coef.", "-" )
972 CALL histdef2d(iff,o_cldl%flag,o_cldl%name, "Low-level cloudiness", "-")
973 CALL histdef2d(iff,o_cldm%flag,o_cldm%name, "Mid-level cloudiness", "-")
974 CALL histdef2d(iff,o_cldh%flag,o_cldh%name, "High-level cloudiness", "-")
975 CALL histdef2d(iff,o_cldt%flag,o_cldt%name, "Total cloudiness", "-")
976 CALL histdef2d(iff,o_cldq%flag,o_cldq%name, "Cloud liquid water path", "kg/m2")
977 CALL histdef2d(iff,o_lwp%flag,o_lwp%name, "Cloud water path", "kg/m2")
978 CALL histdef2d(iff,o_iwp%flag,o_iwp%name, "Cloud ice water path", "kg/m2" )
979 CALL histdef2d(iff,o_ue%flag,o_ue%name, "Zonal energy transport", "-")
980 CALL histdef2d(iff,o_ve%flag,o_ve%name, "Merid energy transport", "-")
981 CALL histdef2d(iff,o_uq%flag,o_uq%name, "Zonal humidity transport", "-")
982 CALL histdef2d(iff,o_vq%flag,o_vq%name, "Merid humidity transport", "-")
983
984     IF(iflag_con.GE.3) THEN ! sb
985 CALL histdef2d(iff,o_cape%flag,o_cape%name, "Conv avlbl pot ener", "J/kg")
986 CALL histdef2d(iff,o_pbase%flag,o_pbase%name, "Cld base pressure", "mb")
987 CALL histdef2d(iff,o_ptop%flag,o_ptop%name, "Cld top pressure", "mb")
988 CALL histdef2d(iff,o_fbase%flag,o_fbase%name, "Cld base mass flux", "kg/m2/s")
989 CALL histdef2d(iff,o_prw%flag,o_prw%name, "Precipitable water", "kg/m2")
990   type_ecri(1) = 't_max(X)'
991   type_ecri(2) = 't_max(X)'
992   type_ecri(3) = 't_max(X)'
993   type_ecri(4) = 't_max(X)'
994   type_ecri(5) = 't_max(X)'
995 CALL histdef2d(iff,o_cape_max%flag,o_cape_max%name, "CAPE max.", "J/kg")
996   type_ecri(:) = type_ecri_files(:)
997 CALL histdef3d(iff,o_upwd%flag,o_upwd%name, "saturated updraft", "kg/m2/s")
998 CALL histdef3d(iff,o_Ma%flag,o_Ma%name, "undilute adiab updraft", "kg/m2/s")
999 CALL histdef3d(iff,o_dnwd%flag,o_dnwd%name, "saturated downdraft", "kg/m2/s")
1000 CALL histdef3d(iff,o_dnwd0%flag,o_dnwd0%name, "unsat. downdraft", "kg/m2/s")
1001 CALL histdef3d(iff,o_mc%flag,o_mc%name, "Convective mass flux", "kg/m2/s")
1002   type_ecri(1) = 'inst(X)'
1003   type_ecri(2) = 'inst(X)'
1004   type_ecri(3) = 'inst(X)'
1005   type_ecri(4) = 'inst(X)'
1006   type_ecri(5) = 'inst(X)'
1007 CALL histdef2d(iff,o_ftime_con%flag,o_ftime_con%name, "Fraction of time convection Occurs", " ")
1008   type_ecri(:) = type_ecri_files(:)
1009     ENDIF !iflag_con .GE. 3
1010
1011 CALL histdef2d(iff,o_s_pblh%flag,o_s_pblh%name, "Boundary Layer Height", "m")
1012 CALL histdef2d(iff,o_s_pblt%flag,o_s_pblt%name, "t at Boundary Layer Height", "K")
1013 CALL histdef2d(iff,o_s_lcl%flag,o_s_lcl%name, "Condensation level", "m")
1014 CALL histdef2d(iff,o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" )
1015 CALL histdef2d(iff,o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2")
1016 CALL histdef2d(iff,o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K")
1017 CALL histdef2d(iff,o_s_therm%flag,o_s_therm%name, "Exces du thermique", "K")
1018 CALL histdef2d(iff,o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2")
1019 CALL histdef2d(iff,o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2")
1020 CALL histdef2d(iff,o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m")
1021
1022! Champs interpolles sur des niveaux de pression
1023
1024   type_ecri(1) = 'inst(X)'
1025   type_ecri(2) = 'inst(X)'
1026   type_ecri(3) = 'inst(X)'
1027   type_ecri(4) = 'inst(X)'
1028   type_ecri(5) = 'inst(X)'
1029
1030! Attention a reverifier
1031
1032        ilev=0       
1033        DO k=1, nlevSTD
1034!     IF(k.GE.2.AND.k.LE.12) bb2=clevSTD(k)
1035     bb2=clevSTD(k)
1036     IF(bb2.EQ."850".OR.bb2.EQ."700".OR.bb2.EQ."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")THEN
1037      ilev=ilev+1
1038      print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name
1039 CALL histdef2d(iff,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name,"Zonal wind "//bb2//"mb", "m/s")
1040 CALL histdef2d(iff,o_vSTDlevs(ilev)%flag,o_vSTDlevs(ilev)%name,"Meridional wind "//bb2//"mb", "m/s")
1041 CALL histdef2d(iff,o_wSTDlevs(ilev)%flag,o_wSTDlevs(ilev)%name,"Vertical wind "//bb2//"mb", "Pa/s")
1042 CALL histdef2d(iff,o_phiSTDlevs(ilev)%flag,o_phiSTDlevs(ilev)%name,"Geopotential "//bb2//"mb", "m")
1043 CALL histdef2d(iff,o_qSTDlevs(ilev)%flag,o_qSTDlevs(ilev)%name,"Specific humidity "//bb2//"mb", "kg/kg" )
1044 CALL histdef2d(iff,o_tSTDlevs(ilev)%flag,o_tSTDlevs(ilev)%name,"Temperature "//bb2//"mb", "K")
1045     ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")
1046       ENDDO
1047   type_ecri(:) = type_ecri_files(:)
1048
1049 CALL histdef2d(iff,o_t_oce_sic%flag,o_t_oce_sic%name, "Temp mixte oce-sic", "K")
1050
1051 IF (type_ocean=='slab') &
1052     CALL histdef2d(iff,o_slab_bils%flag, o_slab_bils%name,"Bilan au sol sur ocean slab", "W/m2")
1053
1054! Couplage conv-CL
1055 IF (iflag_con.GE.3) THEN
1056    IF (iflag_coupl.EQ.1) THEN
1057 CALL histdef2d(iff,o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2")
1058 CALL histdef2d(iff,o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2")
1059    ENDIF
1060 ENDIF !(iflag_con.GE.3)
1061
1062 CALL histdef2d(iff,o_weakinv%flag,o_weakinv%name, "Weak inversion", "-")
1063 CALL histdef2d(iff,o_dthmin%flag,o_dthmin%name, "dTheta mini", "K/m")
1064 CALL histdef2d(iff,o_rh2m%flag,o_rh2m%name, "Relative humidity at 2m", "%" )
1065   type_ecri(1) = 't_min(X)'
1066   type_ecri(2) = 't_min(X)'
1067   type_ecri(3) = 't_min(X)'
1068   type_ecri(4) = 't_min(X)'
1069   type_ecri(5) = 't_min(X)'
1070 CALL histdef2d(iff,o_rh2m_min%flag,o_rh2m_min%name, "Min Relative humidity at 2m", "%" )
1071   type_ecri(1) = 't_max(X)'
1072   type_ecri(2) = 't_max(X)'
1073   type_ecri(3) = 't_max(X)'
1074   type_ecri(4) = 't_max(X)'
1075   type_ecri(5) = 't_max(X)'
1076 CALL histdef2d(iff,o_rh2m_max%flag,o_rh2m_max%name, "Max Relative humidity at 2m", "%" )
1077   type_ecri(:) = type_ecri_files(:)
1078 CALL histdef2d(iff,o_qsat2m%flag,o_qsat2m%name, "Saturant humidity at 2m", "%")
1079 CALL histdef2d(iff,o_tpot%flag,o_tpot%name, "Surface air potential temperature", "K")
1080 CALL histdef2d(iff,o_tpote%flag,o_tpote%name, "Surface air equivalent potential temperature", "K")
1081 CALL histdef2d(iff,o_SWnetOR%flag,o_SWnetOR%name, "Sfce net SW radiation OR", "W/m2")
1082 CALL histdef2d(iff,o_SWdownOR%flag,o_SWdownOR%name, "Sfce incident SW radiation OR", "W/m2")
1083 CALL histdef2d(iff,o_LWdownOR%flag,o_LWdownOR%name, "Sfce incident LW radiation OR", "W/m2")
1084 CALL histdef2d(iff,o_snowl%flag,o_snowl%name, "Solid Large-scale Precip.", "kg/(m2*s)")
1085
1086 CALL histdef2d(iff,o_solldown%flag,o_solldown%name, "Down. IR rad. at surface", "W/m2")
1087 CALL histdef2d(iff,o_dtsvdfo%flag,o_dtsvdfo%name, "Boundary-layer dTs(o)", "K/s")
1088 CALL histdef2d(iff,o_dtsvdft%flag,o_dtsvdft%name, "Boundary-layer dTs(t)", "K/s")
1089 CALL histdef2d(iff,o_dtsvdfg%flag,o_dtsvdfg%name, "Boundary-layer dTs(g)", "K/s")
1090 CALL histdef2d(iff,o_dtsvdfi%flag,o_dtsvdfi%name, "Boundary-layer dTs(g)", "K/s")
1091 CALL histdef2d(iff,o_rugs%flag,o_rugs%name, "rugosity", "-" )
1092
1093! Champs 3D:
1094 CALL histdef3d(iff,o_ec550aer%flag,o_ec550aer%name, "Extinction at 550nm", "m^-1")
1095 CALL histdef3d(iff,o_lwcon%flag,o_lwcon%name, "Cloud liquid water content", "kg/kg")
1096 CALL histdef3d(iff,o_iwcon%flag,o_iwcon%name, "Cloud ice water content", "kg/kg")
1097 CALL histdef3d(iff,o_temp%flag,o_temp%name, "Air temperature", "K" )
1098 CALL histdef3d(iff,o_theta%flag,o_theta%name, "Potential air temperature", "K" )
1099 CALL histdef3d(iff,o_ovap%flag,o_ovap%name, "Specific humidity + dqphy", "kg/kg" )
1100 CALL histdef3d(iff,o_ovapinit%flag,o_ovapinit%name, "Specific humidity", "kg/kg" )
1101 CALL histdef3d(iff,o_geop%flag,o_geop%name, "Geopotential height", "m2/s2")
1102 CALL histdef3d(iff,o_vitu%flag,o_vitu%name, "Zonal wind", "m/s" )
1103 CALL histdef3d(iff,o_vitv%flag,o_vitv%name, "Meridional wind", "m/s" )
1104 CALL histdef3d(iff,o_vitw%flag,o_vitw%name, "Vertical wind", "Pa/s" )
1105 CALL histdef3d(iff,o_pres%flag,o_pres%name, "Air pressure", "Pa" )
1106 CALL histdef3d(iff,o_paprs%flag,o_paprs%name, "Air pressure Inter-Couches", "Pa" )
1107 CALL histdef3d(iff,o_rneb%flag,o_rneb%name, "Cloud fraction", "-")
1108 CALL histdef3d(iff,o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-")
1109 CALL histdef3d(iff,o_rhum%flag,o_rhum%name, "Relative humidity", "-")
1110 CALL histdef3d(iff,o_ozone%flag,o_ozone%name, "Ozone mole fraction", "-")
1111 if (read_climoz == 2) &
1112      CALL histdef3d(iff,o_ozone_light%flag,o_ozone_light%name, &
1113      "Daylight ozone mole fraction", "-")
1114 CALL histdef3d(iff,o_dtphy%flag,o_dtphy%name, "Physics dT", "K/s")
1115 CALL histdef3d(iff,o_dqphy%flag,o_dqphy%name, "Physics dQ", "(kg/kg)/s")
1116 CALL histdef3d(iff,o_cldtau%flag,o_cldtau%name, "Cloud optical thickness", "1")
1117 CALL histdef3d(iff,o_cldemi%flag,o_cldemi%name, "Cloud optical emissivity", "1")
1118!IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl
1119 CALL histdef3d(iff,o_pr_con_l%flag,o_pr_con_l%name, "Convective precipitation lic", " ")
1120 CALL histdef3d(iff,o_pr_con_i%flag,o_pr_con_i%name, "Convective precipitation ice", " ")
1121 CALL histdef3d(iff,o_pr_lsc_l%flag,o_pr_lsc_l%name, "Large scale precipitation lic", " ")
1122 CALL histdef3d(iff,o_pr_lsc_i%flag,o_pr_lsc_i%name, "Large scale precipitation ice", " ")
1123!Cloud droplet effective radius
1124 CALL histdef3d(iff,o_re%flag,o_re%name, "Cloud droplet effective radius","um")
1125 CALL histdef3d(iff,o_fl%flag,o_fl%name, "Denominator of Cloud droplet effective radius"," ")
1126!FH Sorties pour la couche limite
1127     if (iflag_pbl>1) then
1128 CALL histdef3d(iff,o_tke%flag,o_tke%name, "TKE", "m2/s2")
1129   type_ecri(1) = 't_max(X)'
1130   type_ecri(2) = 't_max(X)'
1131   type_ecri(3) = 't_max(X)'
1132   type_ecri(4) = 't_max(X)'
1133   type_ecri(5) = 't_max(X)'
1134 CALL histdef3d(iff,o_tke_max%flag,o_tke_max%name, "TKE max", "m2/s2")
1135   type_ecri(:) = type_ecri_files(:)
1136     endif
1137
1138 CALL histdef3d(iff,o_kz%flag,o_kz%name, "Kz melange", "m2/s")
1139   type_ecri(1) = 't_max(X)'
1140   type_ecri(2) = 't_max(X)'
1141   type_ecri(3) = 't_max(X)'
1142   type_ecri(4) = 't_max(X)'
1143   type_ecri(5) = 't_max(X)'
1144 CALL histdef3d(iff,o_kz_max%flag,o_kz_max%name, "Kz melange max", "m2/s" )
1145   type_ecri(:) = type_ecri_files(:)
1146 CALL histdef3d(iff,o_clwcon%flag,o_clwcon%name, "Convective Cloud Liquid water content", "kg/kg")
1147 CALL histdef3d(iff,o_dtdyn%flag,o_dtdyn%name, "Dynamics dT", "K/s")
1148 CALL histdef3d(iff,o_dqdyn%flag,o_dqdyn%name, "Dynamics dQ", "(kg/kg)/s")
1149 CALL histdef3d(iff,o_dudyn%flag,o_dudyn%name, "Dynamics dU", "m/s2")
1150 CALL histdef3d(iff,o_dvdyn%flag,o_dvdyn%name, "Dynamics dV", "m/s2")
1151 CALL histdef3d(iff,o_dtcon%flag,o_dtcon%name, "Convection dT", "K/s")
1152 CALL histdef3d(iff,o_ducon%flag,o_ducon%name, "Convection du", "m/s2")
1153 CALL histdef3d(iff,o_dqcon%flag,o_dqcon%name, "Convection dQ", "(kg/kg)/s")
1154
1155! Wakes
1156 IF(iflag_con.EQ.3) THEN
1157 IF (iflag_wake == 1) THEN
1158   CALL histdef2d(iff,o_ale_wk%flag,o_ale_wk%name, "ALE WK", "m2/s2")
1159   CALL histdef2d(iff,o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2")
1160   CALL histdef2d(iff,o_ale%flag,o_ale%name, "ALE", "m2/s2")
1161   CALL histdef2d(iff,o_alp%flag,o_alp%name, "ALP", "W/m2")
1162   CALL histdef2d(iff,o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2")
1163   CALL histdef2d(iff,o_wape%flag,o_WAPE%name, "WAPE", "m2/s2")
1164   CALL histdef2d(iff,o_wake_h%flag,o_wake_h%name, "wake_h", "-")
1165   CALL histdef2d(iff,o_wake_s%flag,o_wake_s%name, "wake_s", "-")
1166   CALL histdef3d(iff,o_dtwak%flag,o_dtwak%name, "Wake dT", "K/s")
1167   CALL histdef3d(iff,o_dqwak%flag,o_dqwak%name, "Wake dQ", "(kg/kg)/s")
1168   CALL histdef3d(iff,o_wake_deltat%flag,o_wake_deltat%name, "wake_deltat", " ")
1169   CALL histdef3d(iff,o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ")
1170   CALL histdef3d(iff,o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ")
1171 ENDIF
1172   CALL histdef3d(iff,o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-")
1173   CALL histdef3d(iff,o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-")
1174   CALL histdef3d(iff,o_fqd%flag,o_fqd%name,"tend vap eau due aux descentes precip", "-")
1175 ENDIF !(iflag_con.EQ.3)
1176
1177 CALL histdef3d(iff,o_dtlsc%flag,o_dtlsc%name, "Condensation dT", "K/s")
1178 CALL histdef3d(iff,o_dtlschr%flag,o_dtlschr%name,"Large-scale condensational heating rate","K/s")
1179 CALL histdef3d(iff,o_dqlsc%flag,o_dqlsc%name, "Condensation dQ", "(kg/kg)/s")
1180 CALL histdef3d(iff,o_dtvdf%flag,o_dtvdf%name, "Boundary-layer dT", "K/s")
1181 CALL histdef3d(iff,o_dqvdf%flag,o_dqvdf%name, "Boundary-layer dQ", "(kg/kg)/s")
1182 CALL histdef3d(iff,o_dteva%flag,o_dteva%name, "Reevaporation dT", "K/s")
1183 CALL histdef3d(iff,o_dqeva%flag,o_dqeva%name, "Reevaporation dQ", "(kg/kg)/s")
1184 CALL histdef3d(iff,o_ptconv%flag,o_ptconv%name, "POINTS CONVECTIFS", " ")
1185 CALL histdef3d(iff,o_ratqs%flag,o_ratqs%name, "RATQS", " ")
1186 CALL histdef3d(iff,o_dtthe%flag,o_dtthe%name, "Dry adjust. dT", "K/s")
1187
1188if(iflag_thermals.gt.1) THEN
1189 CALL histdef3d(iff,o_f_th%flag,o_f_th%name, "Thermal plume mass flux", "K/s")
1190 CALL histdef3d(iff,o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s")
1191 CALL histdef3d(iff,o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s")
1192 CALL histdef3d(iff,o_lambda_th%flag,o_lambda_th%name,"Thermal plume vertical velocity","m/s")
1193 CALL histdef2d(iff,o_ftime_th%flag,o_ftime_th%name,"Fraction of time Shallow convection occurs"," ")
1194 CALL histdef3d(iff,o_q_th%flag,o_q_th%name, "Thermal plume total humidity", "kg/kg")
1195 CALL histdef3d(iff,o_a_th%flag,o_a_th%name, "Thermal plume fraction", "")
1196 CALL histdef3d(iff,o_d_th%flag,o_d_th%name, "Thermal plume detrainment", "K/s")
1197endif !iflag_thermals.gt.1
1198 CALL histdef2d(iff,o_f0_th%flag,o_f0_th%name, "Thermal closure mass flux", "K/s")
1199 CALL histdef2d(iff,o_zmax_th%flag,o_zmax_th%name, "Thermal plume height", "K/s")
1200 CALL histdef3d(iff,o_dqthe%flag,o_dqthe%name, "Dry adjust. dQ", "(kg/kg)/s")
1201 CALL histdef3d(iff,o_dtajs%flag,o_dtajs%name, "Dry adjust. dT", "K/s")
1202 CALL histdef3d(iff,o_dqajs%flag,o_dqajs%name, "Dry adjust. dQ", "(kg/kg)/s")
1203 CALL histdef3d(iff,o_dtswr%flag,o_dtswr%name, "SW radiation dT", "K/s")
1204 CALL histdef3d(iff,o_dtsw0%flag,o_dtsw0%name, "CS SW radiation dT", "K/s")
1205 CALL histdef3d(iff,o_dtlwr%flag,o_dtlwr%name, "LW radiation dT", "K/s")
1206 CALL histdef3d(iff,o_dtlw0%flag,o_dtlw0%name, "CS LW radiation dT", "K/s")
1207 CALL histdef3d(iff,o_dtec%flag,o_dtec%name, "Cinetic dissip dT", "K/s")
1208 CALL histdef3d(iff,o_duvdf%flag,o_duvdf%name, "Boundary-layer dU", "m/s2")
1209 CALL histdef3d(iff,o_dvvdf%flag,o_dvvdf%name, "Boundary-layer dV", "m/s2")
1210
1211     IF (ok_orodr) THEN
1212 CALL histdef3d(iff,o_duoro%flag,o_duoro%name, "Orography dU", "m/s2")
1213 CALL histdef3d(iff,o_dvoro%flag,o_dvoro%name, "Orography dV", "m/s2")
1214     ENDIF
1215
1216     IF (ok_orolf) THEN
1217 CALL histdef3d(iff,o_dulif%flag,o_dulif%name, "Orography dU", "m/s2")
1218 CALL histdef3d(iff,o_dvlif%flag,o_dvlif%name, "Orography dV", "m/s2")
1219     ENDIF
1220
1221      if (nqtot>=3) THEN
1222!Attention    DO iq=3,nqtot
1223    DO iq=3,4 
1224       iiq=niadv(iq)
1225! CALL histdef3d (iff, o_trac%flag,'o_'//tnom(iq)%name,ttext(iiq), "-" )
1226  CALL histdef3d (iff, o_trac(iq-2)%flag,o_trac(iq-2)%name,ttext(iiq), "-" )
1227    ENDDO
1228      endif
1229
1230        CALL histend(nid_files(iff))
1231
1232         ndex2d = 0
1233         ndex3d = 0
1234
1235         ENDIF ! clef_files
1236
1237         ENDDO !  iff
1238     print*,'Fin phys_output_mod.F90'
1239      end subroutine phys_output_open
1240
1241      SUBROUTINE histdef2d (iff,flag_var,nomvar,titrevar,unitvar)
1242     
1243       use ioipsl
1244       USE dimphy
1245       USE mod_phys_lmdz_para
1246
1247       IMPLICIT NONE
1248       
1249       include "dimensions.h"
1250       include "temps.h"
1251       include "indicesol.h"
1252       include "clesphys.h"
1253
1254       integer                          :: iff
1255       integer, dimension(nfiles)       :: flag_var
1256       character(len=20)                 :: nomvar
1257       character(len=*)                 :: titrevar
1258       character(len=*)                 :: unitvar
1259
1260       real zstophym
1261
1262       if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
1263         zstophym=zoutm(iff)
1264       else
1265         zstophym=zdtime
1266       endif
1267
1268! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
1269       call conf_physoutputs(nomvar,flag_var)
1270       
1271       if ( flag_var(iff)<=lev_files(iff) ) then
1272 call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
1273               iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
1274               type_ecri(iff), zstophym,zoutm(iff))               
1275       endif                     
1276      end subroutine histdef2d
1277
1278      SUBROUTINE histdef3d (iff,flag_var,nomvar,titrevar,unitvar)
1279
1280       use ioipsl
1281       USE dimphy
1282       USE mod_phys_lmdz_para
1283
1284       IMPLICIT NONE
1285
1286       include "dimensions.h"
1287       include "temps.h"
1288       include "indicesol.h"
1289       include "clesphys.h"
1290
1291       integer                          :: iff
1292       integer, dimension(nfiles)       :: flag_var
1293       character(len=20)                 :: nomvar
1294       character(len=*)                 :: titrevar
1295       character(len=*)                 :: unitvar
1296
1297       real zstophym
1298
1299! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
1300       call conf_physoutputs(nomvar,flag_var)
1301
1302       if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
1303         zstophym=zoutm(iff)
1304       else
1305         zstophym=zdtime
1306       endif
1307
1308       if ( flag_var(iff)<=lev_files(iff) ) then
1309          call histdef (nid_files(iff), nomvar, titrevar, unitvar, &
1310               iim, jj_nb, nhorim(iff), klev, levmin(iff), &
1311               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), &
1312               zstophym, zoutm(iff))
1313       endif
1314      end subroutine histdef3d
1315
1316      SUBROUTINE conf_physoutputs(nam_var,flag_var)
1317!!! Lecture des noms et niveau de sortie des variables dans output.def
1318!   en utilisant les routines getin de IOIPSL 
1319       use ioipsl
1320
1321       IMPLICIT NONE
1322
1323       include 'iniprint.h'
1324
1325       character(len=20)                :: nam_var
1326       integer, dimension(nfiles)      :: flag_var
1327
1328        IF(prt_level>10) WRITE(lunout,*)'Avant getin: nam_var flag_var ',nam_var,flag_var(:)
1329        call getin('flag_'//nam_var,flag_var)
1330        call getin('name_'//nam_var,nam_var)
1331        IF(prt_level>10) WRITE(lunout,*)'Apres getin: nam_var flag_var ',nam_var,flag_var(:)
1332
1333      END SUBROUTINE conf_physoutputs
1334
1335      SUBROUTINE convers_timesteps(str,timestep)
1336
1337        use ioipsl
1338
1339        IMPLICIT NONE
1340
1341        character(len=20)   :: str
1342        character(len=10)   :: type
1343        integer             :: ipos,il
1344        real                :: ttt,xxx,timestep,dayseconde
1345        parameter (dayseconde=86400.)
1346        include "temps.h"
1347        include "comconst.h"
1348
1349        ipos=scan(str,'0123456789.',.true.)
1350
1351        il=len_trim(str)
1352        print*,ipos,il
1353        read(str(1:ipos),*) ttt
1354        print*,ttt
1355        type=str(ipos+1:il)
1356
1357
1358        if ( il == ipos ) then
1359        type='day'
1360        endif
1361
1362        if ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde
1363        if ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then
1364           print*,'annee_ref,day_ref mon_len',annee_ref,day_ref,ioget_mon_len(annee_ref,day_ref)
1365           timestep = ttt * dayseconde * ioget_mon_len(annee_ref,day_ref)
1366        endif
1367        if ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.
1368        if ( type == 'mn'.or.type == 'minutes'  ) timestep = ttt * 60.
1369        if ( type == 's'.or.type == 'sec'.or.type == 'secondes'   ) timestep = ttt
1370        if ( type == 'TS' ) timestep = dtphys
1371
1372        print*,'type =      ',type
1373        print*,'nb j/h/m =  ',ttt
1374        print*,'timestep(s)=',timestep
1375
1376        END SUBROUTINE convers_timesteps
1377
1378END MODULE phys_output_mod
1379
Note: See TracBrowser for help on using the repository browser.