source: LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/phys_output_mod.F90 @ 1389

Last change on this file since 1389 was 1389, checked in by Laurent Fairhead, 14 years ago
  • Differing COMPLEX declarations were causing problems in FFT routines

compilation. The FFTs should only be used in double precision in any case

  • the ALLOCATE command for the o_trac variable was misplaced and called

several times (causing an error for some compilators)


  • Des déclarations COMPLEX différenciées causaient des problèmes de

compilation dans les routines des filtres FFT. Celles-ci ne devraient être
utilisées qu'en double précision de toutes façons.

  • L'ALLOCATE de la variable o_trac était mal placé et appelé plusieurs fois

(ce qui causait des crash pour certains compilateurs)

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