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

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

Changes in output options for aerosols


Changements dans les options de sorties pour les aerosols

ACo

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