source: LMDZ4/branches/LMDZ4-dev/libf/phylmd/phys_output_mod.F90 @ 1226

Last change on this file since 1226 was 1218, checked in by idelkadi, 15 years ago

Corrections dans la lecture des frequences de sorties dans les fichiers histoirs :
Possibilite de lire les frequences en Nombre :

  • de mois (mth, mounths, mous),
  • de jours(day, days, jours)
  • de minutes (mn, minutes),
  • d'heures (hours, hr, heures),
  • de minutes (mn, minutes),
  • de secondes (s, sec, secondes) et
  • de pas de temps de la physiqe ( TS )
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 65.5 KB
Line 
1!
2! $Id: phys_output_mod.F90 1218 2009-07-29 14:21:48Z jghattas $
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((/ 4, 10, 10, 10, 10 /),'topswad')
342  type(ctrl_out),save :: o_topswai      = ctrl_out((/ 4, 10, 10, 10, 10 /),'topswai')
343  type(ctrl_out),save :: o_solswad      = ctrl_out((/ 4, 10, 10, 10, 10 /),'solswad')
344  type(ctrl_out),save :: o_solswai      = ctrl_out((/ 4, 10, 10, 10, 10 /),'solswai')
345!!!!!!!!!!!!!!!!!!!!!! 3D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
346  type(ctrl_out),save :: o_lwcon        = ctrl_out((/ 2, 5, 10, 10, 1 /),'lwcon')
347  type(ctrl_out),save :: o_iwcon        = ctrl_out((/ 2, 5, 10, 10, 10 /),'iwcon')
348  type(ctrl_out),save :: o_temp         = ctrl_out((/ 2, 3, 4, 1, 1 /),'temp')
349  type(ctrl_out),save :: o_theta        = ctrl_out((/ 2, 3, 4, 1, 1 /),'theta')
350  type(ctrl_out),save :: o_ovap         = ctrl_out((/ 2, 3, 4, 1, 1 /),'ovap')
351  type(ctrl_out),save :: o_ovapinit         = ctrl_out((/ 2, 3, 4, 1, 1 /),'ovapinit')
352  type(ctrl_out),save :: o_wvapp        = ctrl_out((/ 2, 10, 10, 10, 10 /),'wvapp')
353  type(ctrl_out),save :: o_geop         = ctrl_out((/ 2, 3, 10, 1, 1 /),'geop')
354  type(ctrl_out),save :: o_vitu         = ctrl_out((/ 2, 3, 4, 1, 1 /),'vitu')
355  type(ctrl_out),save :: o_vitv         = ctrl_out((/ 2, 3, 4, 1, 1 /),'vitv')
356  type(ctrl_out),save :: o_vitw         = ctrl_out((/ 2, 3, 10, 10, 1 /),'vitw')
357  type(ctrl_out),save :: o_pres         = ctrl_out((/ 2, 3, 10, 1, 1 /),'pres')
358  type(ctrl_out),save :: o_rneb         = ctrl_out((/ 2, 5, 10, 10, 1 /),'rneb')
359  type(ctrl_out),save :: o_rnebcon      = ctrl_out((/ 2, 5, 10, 10, 1 /),'rnebcon')
360  type(ctrl_out),save :: o_rhum         = ctrl_out((/ 2, 10, 10, 10, 10 /),'rhum')
361  type(ctrl_out),save :: o_ozone        = ctrl_out((/ 2, 10, 10, 10, 10 /),'ozone')
362  type(ctrl_out),save :: o_upwd         = ctrl_out((/ 2, 10, 10, 10, 10 /),'upwd')
363  type(ctrl_out),save :: o_dtphy        = ctrl_out((/ 2, 10, 10, 10, 1 /),'dtphy')
364  type(ctrl_out),save :: o_dqphy        = ctrl_out((/ 2, 10, 10, 10, 1 /),'dqphy')
365  type(ctrl_out),save :: o_pr_con_l     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_con_l')
366  type(ctrl_out),save :: o_pr_con_i     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_con_i')
367  type(ctrl_out),save :: o_pr_lsc_l     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_lsc_l')
368  type(ctrl_out),save :: o_pr_lsc_i     = ctrl_out((/ 2, 10, 10, 10, 10 /),'pr_lsc_i')
369!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
370
371  type(ctrl_out),save,dimension(4) :: o_albe_srf     = (/ ctrl_out((/ 3, 4, 10, 1, 10 /),'albe_ter'), &
372                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'albe_lic'), &
373                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'albe_oce'), &
374                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'albe_sic') /)
375
376  type(ctrl_out),save,dimension(4) :: o_ages_srf     = (/ ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_ter'), &
377                                                     ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_lic'), &
378                                                     ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_oce'), &
379                                                     ctrl_out((/ 3, 10, 10, 10, 10 /),'ages_sic') /)
380
381  type(ctrl_out),save,dimension(4) :: o_rugs_srf     = (/ ctrl_out((/ 3, 4, 10, 1, 10 /),'rugs_ter'), &
382                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'rugs_lic'), &
383                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'rugs_oce'), &
384                                                     ctrl_out((/ 3, 4, 10, 1, 10 /),'rugs_sic') /)
385
386  type(ctrl_out),save :: o_albs         = ctrl_out((/ 3, 10, 10, 1, 10 /),'albs')
387  type(ctrl_out),save :: o_albslw       = ctrl_out((/ 3, 10, 10, 1, 10 /),'albslw')
388
389  type(ctrl_out),save :: o_clwcon       = ctrl_out((/ 4, 10, 10, 10, 10 /),'clwcon')
390  type(ctrl_out),save :: o_Ma           = ctrl_out((/ 4, 10, 10, 10, 10 /),'Ma')
391  type(ctrl_out),save :: o_dnwd         = ctrl_out((/ 4, 10, 10, 10, 10 /),'dnwd')
392  type(ctrl_out),save :: o_dnwd0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dnwd0')
393  type(ctrl_out),save :: o_dtdyn        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dtdyn')
394  type(ctrl_out),save :: o_dqdyn        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dqdyn')
395  type(ctrl_out),save :: o_dudyn        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dudyn')  !AXC
396  type(ctrl_out),save :: o_dvdyn        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dvdyn')  !AXC
397  type(ctrl_out),save :: o_dtcon        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dtcon')
398  type(ctrl_out),save :: o_ducon        = ctrl_out((/ 4, 10, 10, 10, 10 /),'ducon')
399  type(ctrl_out),save :: o_dqcon        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dqcon')
400  type(ctrl_out),save :: o_dtwak        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dtwak')
401  type(ctrl_out),save :: o_dqwak        = ctrl_out((/ 4, 5, 10, 10, 10 /),'dqwak')
402  type(ctrl_out),save :: o_wake_h       = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_h')
403  type(ctrl_out),save :: o_wake_s       = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_s')
404  type(ctrl_out),save :: o_wake_deltat  = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_deltat')
405  type(ctrl_out),save :: o_wake_deltaq  = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_deltaq')
406  type(ctrl_out),save :: o_wake_omg     = ctrl_out((/ 4, 5, 10, 10, 10 /),'wake_omg')
407  type(ctrl_out),save :: o_Vprecip      = ctrl_out((/ 10, 10, 10, 10, 10 /),'Vprecip')
408  type(ctrl_out),save :: o_ftd          = ctrl_out((/ 4, 5, 10, 10, 10 /),'ftd')
409  type(ctrl_out),save :: o_fqd          = ctrl_out((/ 4, 5, 10, 10, 10 /),'fqd')
410  type(ctrl_out),save :: o_dtlsc        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlsc')
411  type(ctrl_out),save :: o_dtlschr      = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlschr')
412  type(ctrl_out),save :: o_dqlsc        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqlsc')
413  type(ctrl_out),save :: o_dtvdf        = ctrl_out((/ 4, 10, 10, 1, 10 /),'dtvdf')
414  type(ctrl_out),save :: o_dqvdf        = ctrl_out((/ 4, 10, 10, 1, 10 /),'dqvdf')
415  type(ctrl_out),save :: o_dteva        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dteva')
416  type(ctrl_out),save :: o_dqeva        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqeva')
417  type(ctrl_out),save :: o_ptconv       = ctrl_out((/ 4, 10, 10, 10, 10 /),'ptconv')
418  type(ctrl_out),save :: o_ratqs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'ratqs')
419  type(ctrl_out),save :: o_dtthe        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtthe')
420  type(ctrl_out),save :: o_f_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'f_th')
421  type(ctrl_out),save :: o_e_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'e_th')
422  type(ctrl_out),save :: o_w_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'w_th')
423  type(ctrl_out),save :: o_lambda_th    = ctrl_out((/ 10, 10, 10, 10, 10 /),'lambda_th')
424  type(ctrl_out),save :: o_q_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'q_th')
425  type(ctrl_out),save :: o_a_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'a_th')
426  type(ctrl_out),save :: o_d_th         = ctrl_out((/ 4, 10, 10, 10, 10 /),'d_th')
427  type(ctrl_out),save :: o_f0_th        = ctrl_out((/ 4, 10, 10, 10, 10 /),'f0_th')
428  type(ctrl_out),save :: o_zmax_th      = ctrl_out((/ 4, 10, 10, 10, 10 /),'zmax_th')
429  type(ctrl_out),save :: o_dqthe        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dqthe')
430  type(ctrl_out),save :: o_dtajs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtajs')
431  type(ctrl_out),save :: o_dqajs        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dqajs')
432  type(ctrl_out),save :: o_dtswr        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dtswr')
433  type(ctrl_out),save :: o_dtsw0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtsw0')
434  type(ctrl_out),save :: o_dtlwr        = ctrl_out((/ 4, 10, 10, 10, 1 /),'dtlwr')
435  type(ctrl_out),save :: o_dtlw0        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtlw0')
436  type(ctrl_out),save :: o_dtec         = ctrl_out((/ 4, 10, 10, 10, 10 /),'dtec')
437  type(ctrl_out),save :: o_duvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'duvdf')
438  type(ctrl_out),save :: o_dvvdf        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvvdf')
439  type(ctrl_out),save :: o_duoro        = ctrl_out((/ 4, 10, 10, 10, 10 /),'duoro')
440  type(ctrl_out),save :: o_dvoro        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvoro')
441  type(ctrl_out),save :: o_dulif        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dulif')
442  type(ctrl_out),save :: o_dvlif        = ctrl_out((/ 4, 10, 10, 10, 10 /),'dvlif')
443
444! Attention a refaire correctement
445  type(ctrl_out),save,dimension(2) :: o_trac         = (/ ctrl_out((/ 4, 10, 10, 10, 10 /),'trac01'), &
446                                                     ctrl_out((/ 4, 10, 10, 10, 10 /),'trac02') /)
447    CONTAINS
448
449!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
450!!!!!!!!! Ouverture des fichier et definition des variable de sortie !!!!!!!!
451!! histbeg, histvert et histdef
452!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
453 
454  SUBROUTINE phys_output_open(jjmp1,nlevSTD,clevSTD,nbteta, &
455                              ctetaSTD,dtime, ok_veget, &
456                              type_ocean, iflag_pbl,ok_mensuel,ok_journe, &
457                              ok_hf,ok_instan,ok_LES,ok_ade,ok_aie)   
458
459  USE iophy
460  USE dimphy
461  USE infotrac
462  USE ioipsl
463  USE mod_phys_lmdz_para
464
465  IMPLICIT NONE
466  include "dimensions.h"
467  include "temps.h"
468  include "indicesol.h"
469  include "clesphys.h"
470  include "thermcell.h"
471  include "comvert.h"
472
473  integer                               :: jjmp1
474  integer                               :: nbteta, nlevSTD, radpas
475  logical                               :: ok_mensuel, ok_journe, ok_hf, ok_instan
476  logical                               :: ok_LES,ok_ade,ok_aie
477  real                                  :: dtime
478  integer                               :: idayref
479  real                                  :: zjulian
480  real, dimension(klev)                 :: Ahyb, Bhyb, Alt
481  character(len=4), dimension(nlevSTD)  :: clevSTD
482  integer                               :: nsrf, k, iq, iiq, iff, i, j, ilev
483  logical                               :: ok_veget
484  integer                               :: iflag_pbl
485  CHARACTER(len=4)                      :: bb2
486  CHARACTER(len=2)                      :: bb3
487  character(len=6)                      :: type_ocean
488  CHARACTER(len=3)                      :: ctetaSTD(nbteta)
489  real, dimension(nfiles)               :: ecrit_files
490  CHARACTER(len=20), dimension(nfiles)  :: name_files
491  INTEGER, dimension(iim*jjmp1)         ::  ndex2d
492  INTEGER, dimension(iim*jjmp1*klev)    :: ndex3d
493  integer                               :: imin_ins, imax_ins
494  integer                               :: jmin_ins, jmax_ins
495  CHARACTER(len=20), dimension(nfiles)  :: type_ecri_files
496  character(len=20), dimension(nfiles)  :: chtimestep   = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq' /)
497
498!!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
499!                 entre [lonmin_reg,lonmax_reg] et [latmin_reg,latmax_reg]
500
501  logical, dimension(nfiles), save  :: ok_reglim         = (/ .false., .false., .false., .false., .true. /)
502  real, dimension(nfiles), save     :: lonmin_reg        = (/ 0., -45., 0., 0., -162. /)
503  real, dimension(nfiles), save     :: lonmax_reg        = (/ 90., 45., 90., 90., -144. /)
504  real, dimension(nfiles), save     :: latmin_reg        = (/ 0., -45., 0., 0., 7. /)
505  real, dimension(nfiles), save     :: latmax_reg        = (/ 90., 90., 90., 90., 21. /)
506
507!
508   print*,'Debut phys_output_mod.F90'
509! Initialisations (Valeurs par defaut
510   levmax = (/ klev, klev, klev, klev, klev /)
511
512   name_files(1) = 'histmth'
513   name_files(2) = 'histday'
514   name_files(3) = 'histhf'
515   name_files(4) = 'histins'
516   name_files(5) = 'histLES'
517
518   type_ecri(1) = 'ave(X)'
519   type_ecri(2) = 'ave(X)'
520   type_ecri(3) = 'ave(X)'
521   type_ecri(4) = 'inst(X)'
522   type_ecri(5) = 'inst(X)'
523
524   clef_files(1) = ok_mensuel
525   clef_files(2) = ok_journe
526   clef_files(3) = ok_hf
527   clef_files(4) = ok_instan
528   clef_files(5) = ok_LES
529
530   lev_files(1) = lev_histmth
531   lev_files(2) = lev_histday
532   lev_files(3) = lev_histhf
533   lev_files(4) = 1
534   lev_files(5) = 1
535
536
537   ecrit_files(1) = ecrit_mth
538   ecrit_files(2) = ecrit_day
539   ecrit_files(3) = ecrit_hf
540   ecrit_files(4) = ecrit_ins
541   ecrit_files(5) = ecrit_LES
542 
543!! Lectures des parametres de sorties dans physiq.def
544
545   call getin('phys_out_regfkey',ok_reglim)
546   call getin('phys_out_lonmin',lonmin_reg)
547   call getin('phys_out_lonmax',lonmax_reg)
548   call getin('phys_out_latmin',latmin_reg)
549   call getin('phys_out_latmax',latmax_reg)
550   call getin('phys_out_levmin',levmin)
551   call getin('phys_out_levmax',levmax)
552   call getin('phys_out_filenames',name_files)
553   call getin('phys_out_filekeys',clef_files)
554   call getin('phys_out_filelevels',lev_files)
555   call getin('phys_out_filetimesteps',chtimestep)
556   call getin('phys_out_filetypes',type_ecri_files)
557
558   type_ecri_files(:)=type_ecri(:)
559
560   print*,'phys_out_lonmin=',lonmin_reg
561   print*,'phys_out_lonmax=',lonmax_reg
562   print*,'phys_out_latmin=',latmin_reg
563   print*,'phys_out_latmax=',latmax_reg
564   print*,'phys_out_filenames=',name_files
565   print*,'phys_out_filetypes=',type_ecri
566   print*,'phys_out_filekeys=',clef_files
567   print*,'phys_out_filelevels=',lev_files
568
569!!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
570! Appel de histbeg et histvert pour creer le fichier et les niveaux verticaux !!
571! Appel des histbeg pour definir les variables (nom, moy ou inst, freq de sortie ..
572!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
573
574 zdtime = dtime         ! Frequence ou l on moyenne
575
576! Calcul des Ahyb, Bhyb et Alt
577         do k=1,klev
578          Ahyb(k)=(ap(k)+ap(k+1))/2.
579          Bhyb(k)=(bp(k)+bp(k+1))/2.
580          Alt(k)=log(preff/presnivs(k))*8.
581         enddo
582!          if(prt_level.ge.1) then
583           print*,'Ap Hybrid = ',Ahyb(1:klev)
584           print*,'Bp Hybrid = ',Bhyb(1:klev)
585           print*,'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)
586!          endif
587 DO iff=1,nfiles
588
589    IF (clef_files(iff)) THEN
590
591      if ( chtimestep(iff).eq.'DefFreq' ) then
592! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf ...)*86400.
593        ecrit_files(iff)=ecrit_files(iff)*86400.
594      else
595        call convers_timesteps(chtimestep(iff),ecrit_files(iff))
596      endif
597       print*,'ecrit_files(',iff,')= ',ecrit_files(iff)
598
599      zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde
600
601      idayref = day_ref
602      CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
603
604!!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !!
605!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
606     if (ok_reglim(iff)) then
607
608        imin_ins=1
609        imax_ins=iim
610        jmin_ins=1
611        jmax_ins=jjmp1
612
613! correction abderr       
614        do i=1,iim
615           print*,'io_lon(i)=',io_lon(i)
616           if (io_lon(i).le.lonmin_reg(iff)) imin_ins=i
617           if (io_lon(i).le.lonmax_reg(iff)) imax_ins=i+1
618        enddo
619
620        do j=1,jjmp1
621            print*,'io_lat(j)=',io_lat(j)
622            if (io_lat(j).ge.latmin_reg(iff)) jmax_ins=j+1
623            if (io_lat(j).ge.latmax_reg(iff)) jmin_ins=j
624        enddo
625
626        print*,'On stoke le fichier histoire numero ',iff,' sur ', &
627         imin_ins,imax_ins,jmin_ins,jmax_ins
628         print*,'longitudes : ', &
629         io_lon(imin_ins),io_lon(imax_ins), &
630         'latitudes : ', &
631         io_lat(jmax_ins),io_lat(jmin_ins)
632
633 CALL histbeg(name_files(iff),iim,io_lon,jjmp1,io_lat, &
634              imin_ins,imax_ins-imin_ins+1, &
635              jmin_ins,jmax_ins-jmin_ins+1, &
636              itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
637!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
638       else
639 CALL histbeg_phy(name_files(iff),itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff))
640       endif
641 
642      CALL histvert(nid_files(iff), "presnivs", "Vertical levels", "mb", &
643           levmax(iff) - levmin(iff) + 1, &
644           presnivs(levmin(iff):levmax(iff))/100., nvertm(iff))
645
646!!!!!!!!!!!!! Traitement des champs 3D pour histhf !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
647!!!!!!!!!!!!!!! A Revoir plus tard !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
648!          IF (iff.eq.3.and.lev_files(iff).ge.4) THEN
649!          CALL histbeg_phy("histhf3d",itau_phy, &
650!     &                     zjulian, dtime, &
651!     &                     nhorim, nid_hf3d)
652
653!         CALL histvert(nid_hf3d, "presnivs", &
654!     &                 "Vertical levels", "mb", &
655!     &                 klev, presnivs/100., nvertm)
656!          ENDIF
657!
658!!!! Composentes de la coordonnee sigma-hybride
659   CALL histvert(nid_files(iff), "Ahyb","Ahyb comp of Hyb Cord ", "Pa", &
660                 levmax(iff) - levmin(iff) + 1,Ahyb,nvertap(iff))
661
662   CALL histvert(nid_files(iff), "Bhyb","Bhyb comp of Hyb Cord", " ", &
663                 levmax(iff) - levmin(iff) + 1,Bhyb,nvertbp(iff))
664
665   CALL histvert(nid_files(iff), "Alt","Height approx for scale heigh of 8km at levels", "Km", &
666                 levmax(iff) - levmin(iff) + 1,Alt,nvertAlt(iff))
667
668!   CALL histvert(nid_files(iff), "preff","Reference pressure", "Pa", &
669!                 1,preff,nvertp0(iff))
670!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
671 CALL histdef2d(iff,o_phis%flag,o_phis%name,"Surface geop.height", "m2/s2")
672   type_ecri(1) = 'once'
673   type_ecri(2) = 'once'
674   type_ecri(3) = 'once'
675   type_ecri(4) = 'once'
676   type_ecri(5) = 'once'
677 CALL histdef2d(iff,o_aire%flag,o_aire%name,"Grid area", "-")
678 CALL histdef2d(iff,o_contfracATM%flag,o_contfracATM%name,"% sfce ter+lic", "-")
679   type_ecri(:) = type_ecri_files(:)
680
681!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
682 CALL histdef2d(iff,o_contfracOR%flag,o_contfracOR%name,"% sfce terre OR", "-" )
683 CALL histdef2d(iff,o_aireTER%flag,o_aireTER%name,"Grid area CONT", "-" )
684 CALL histdef2d(iff,o_flat%flag,o_flat%name, "Latent heat flux", "W/m2")
685 CALL histdef2d(iff,o_slp%flag,o_slp%name, "Sea Level Pressure", "Pa" )
686 CALL histdef2d(iff,o_tsol%flag,o_tsol%name, "Surface Temperature", "K")
687 CALL histdef2d(iff,o_t2m%flag,o_t2m%name, "Temperature 2m", "K" )
688   type_ecri(1) = 't_min(X)'
689   type_ecri(2) = 't_min(X)'
690   type_ecri(3) = 't_min(X)'
691   type_ecri(4) = 't_min(X)'
692   type_ecri(5) = 't_min(X)'
693 CALL histdef2d(iff,o_t2m_min%flag,o_t2m_min%name, "Temp 2m min", "K" )
694   type_ecri(1) = 't_max(X)'
695   type_ecri(2) = 't_max(X)'
696   type_ecri(3) = 't_max(X)'
697   type_ecri(4) = 't_max(X)'
698   type_ecri(5) = 't_max(X)'
699 CALL histdef2d(iff,o_t2m_max%flag,o_t2m_max%name, "Temp 2m max", "K" )
700   type_ecri(:) = type_ecri_files(:)
701 CALL histdef2d(iff,o_wind10m%flag,o_wind10m%name, "10-m wind speed", "m/s")
702 CALL histdef2d(iff,o_wind10max%flag,o_wind10max%name, "10m wind speed max", "m/s")
703 CALL histdef2d(iff,o_sicf%flag,o_sicf%name, "Sea-ice fraction", "-" )
704 CALL histdef2d(iff,o_q2m%flag,o_q2m%name, "Specific humidity 2m", "kg/kg")
705 CALL histdef2d(iff,o_u10m%flag,o_u10m%name, "Vent zonal 10m", "m/s" )
706 CALL histdef2d(iff,o_v10m%flag,o_v10m%name, "Vent meridien 10m", "m/s")
707 CALL histdef2d(iff,o_psol%flag,o_psol%name, "Surface Pressure", "Pa" )
708 CALL histdef2d(iff,o_qsurf%flag,o_qsurf%name, "Surface Air humidity", "kg/kg")
709
710  if (.not. ok_veget) then
711 CALL histdef2d(iff,o_qsol%flag,o_qsol%name, "Soil watter content", "mm" )
712  endif
713
714 CALL histdef2d(iff,o_ndayrain%flag,o_ndayrain%name, "Number of dayrain(liq+sol)", "-")
715 CALL histdef2d(iff,o_precip%flag,o_precip%name, "Precip Totale liq+sol", "kg/(s*m2)" )
716 CALL histdef2d(iff,o_plul%flag,o_plul%name, "Large-scale Precip.", "kg/(s*m2)")
717 CALL histdef2d(iff,o_pluc%flag,o_pluc%name, "Convective Precip.", "kg/(s*m2)")
718 CALL histdef2d(iff,o_snow%flag,o_snow%name, "Snow fall", "kg/(s*m2)" )
719 CALL histdef2d(iff,o_evap%flag,o_evap%name, "Evaporat", "kg/(s*m2)" )
720 CALL histdef2d(iff,o_tops%flag,o_tops%name, "Solar rad. at TOA", "W/m2")
721 CALL histdef2d(iff,o_tops0%flag,o_tops0%name, "CS Solar rad. at TOA", "W/m2")
722 CALL histdef2d(iff,o_topl%flag,o_topl%name, "IR rad. at TOA", "W/m2" )
723 CALL histdef2d(iff,o_topl0%flag,o_topl0%name, "IR rad. at TOA", "W/m2")
724 CALL histdef2d(iff,o_SWupTOA%flag,o_SWupTOA%name, "SWup at TOA", "W/m2")
725 CALL histdef2d(iff,o_SWupTOAclr%flag,o_SWupTOAclr%name, "SWup clear sky at TOA", "W/m2")
726 CALL histdef2d(iff,o_SWdnTOA%flag,o_SWdnTOA%name, "SWdn at TOA", "W/m2" )
727 CALL histdef2d(iff,o_SWdnTOAclr%flag,o_SWdnTOAclr%name, "SWdn clear sky at TOA", "W/m2")
728 CALL histdef2d(iff,o_SWup200%flag,o_SWup200%name, "SWup at 200mb", "W/m2" )
729 CALL histdef2d(iff,o_SWup200clr%flag,o_SWup200clr%name, "SWup clear sky at 200mb", "W/m2")
730 CALL histdef2d(iff,o_SWdn200%flag,o_SWdn200%name, "SWdn at 200mb", "W/m2" )
731 CALL histdef2d(iff,o_SWdn200clr%flag,o_SWdn200clr%name, "SWdn clear sky at 200mb", "W/m2")
732 CALL histdef2d(iff,o_LWup200%flag,o_LWup200%name, "LWup at 200mb", "W/m2")
733 CALL histdef2d(iff,o_LWup200clr%flag,o_LWup200clr%name, "LWup clear sky at 200mb", "W/m2")
734 CALL histdef2d(iff,o_LWdn200%flag,o_LWdn200%name, "LWdn at 200mb", "W/m2")
735 CALL histdef2d(iff,o_LWdn200clr%flag,o_LWdn200clr%name, "LWdn clear sky at 200mb", "W/m2")
736 CALL histdef2d(iff,o_sols%flag,o_sols%name, "Solar rad. at surf.", "W/m2")
737 CALL histdef2d(iff,o_sols0%flag,o_sols0%name, "Solar rad. at surf.", "W/m2")
738 CALL histdef2d(iff,o_soll%flag,o_soll%name, "IR rad. at surface", "W/m2") 
739 CALL histdef2d(iff,o_radsol%flag,o_radsol%name, "Rayonnement au sol", "W/m2")
740 CALL histdef2d(iff,o_soll0%flag,o_soll0%name, "IR rad. at surface", "W/m2")
741 CALL histdef2d(iff,o_SWupSFC%flag,o_SWupSFC%name, "SWup at surface", "W/m2")
742 CALL histdef2d(iff,o_SWupSFCclr%flag,o_SWupSFCclr%name, "SWup clear sky at surface", "W/m2")
743 CALL histdef2d(iff,o_SWdnSFC%flag,o_SWdnSFC%name, "SWdn at surface", "W/m2")
744 CALL histdef2d(iff,o_SWdnSFCclr%flag,o_SWdnSFCclr%name, "SWdn clear sky at surface", "W/m2")
745 CALL histdef2d(iff,o_LWupSFC%flag,o_LWupSFC%name, "Upwd. IR rad. at surface", "W/m2")
746 CALL histdef2d(iff,o_LWdnSFC%flag,o_LWdnSFC%name, "Down. IR rad. at surface", "W/m2")
747 CALL histdef2d(iff,o_LWupSFCclr%flag,o_LWupSFCclr%name, "CS Upwd. IR rad. at surface", "W/m2")
748 CALL histdef2d(iff,o_LWdnSFCclr%flag,o_LWdnSFCclr%name, "Down. CS IR rad. at surface", "W/m2")
749 CALL histdef2d(iff,o_bils%flag,o_bils%name, "Surf. total heat flux", "W/m2")
750 CALL histdef2d(iff,o_sens%flag,o_sens%name, "Sensible heat flux", "W/m2")
751 CALL histdef2d(iff,o_fder%flag,o_fder%name, "Heat flux derivation", "W/m2")
752 CALL histdef2d(iff,o_ffonte%flag,o_ffonte%name, "Thermal flux for snow melting", "W/m2")
753 CALL histdef2d(iff,o_fqcalving%flag,o_fqcalving%name, "Ice Calving", "kg/m2/s")
754 CALL histdef2d(iff,o_fqfonte%flag,o_fqfonte%name, "Land ice melt", "kg/m2/s")
755
756     DO nsrf = 1, nbsrf
757 CALL histdef2d(iff,o_pourc_srf(nsrf)%flag,o_pourc_srf(nsrf)%name,"% "//clnsurf(nsrf),"%")
758 CALL histdef2d(iff,o_fract_srf(nsrf)%flag,o_fract_srf(nsrf)%name,"Fraction "//clnsurf(nsrf),"1")
759 CALL histdef2d(iff,o_taux_srf(nsrf)%flag,o_taux_srf(nsrf)%name,"Zonal wind stress"//clnsurf(nsrf),"Pa")
760 CALL histdef2d(iff,o_tauy_srf(nsrf)%flag,o_tauy_srf(nsrf)%name,"Meridional wind stress "//clnsurf(nsrf),"Pa")
761 CALL histdef2d(iff,o_tsol_srf(nsrf)%flag,o_tsol_srf(nsrf)%name,"Temperature "//clnsurf(nsrf),"K")
762 CALL histdef2d(iff,o_u10m_srf(nsrf)%flag,o_u10m_srf(nsrf)%name,"Vent Zonal 10m "//clnsurf(nsrf),"m/s")
763 CALL histdef2d(iff,o_v10m_srf(nsrf)%flag,o_v10m_srf(nsrf)%name,"Vent meredien 10m "//clnsurf(nsrf),"m/s")
764 CALL histdef2d(iff,o_t2m_srf(nsrf)%flag,o_t2m_srf(nsrf)%name,"Temp 2m "//clnsurf(nsrf),"K")
765 CALL histdef2d(iff,o_sens_srf(nsrf)%flag,o_sens_srf(nsrf)%name,"Sensible heat flux "//clnsurf(nsrf),"W/m2")
766 CALL histdef2d(iff,o_lat_srf(nsrf)%flag,o_lat_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
767 CALL histdef2d(iff,o_flw_srf(nsrf)%flag,o_flw_srf(nsrf)%name,"LW "//clnsurf(nsrf),"W/m2")
768 CALL histdef2d(iff,o_fsw_srf(nsrf)%flag,o_fsw_srf(nsrf)%name,"SW "//clnsurf(nsrf),"W/m2")
769 CALL histdef2d(iff,o_wbils_srf(nsrf)%flag,o_wbils_srf(nsrf)%name,"Bilan sol "//clnsurf(nsrf),"W/m2" )
770 CALL histdef2d(iff,o_wbilo_srf(nsrf)%flag,o_wbilo_srf(nsrf)%name,"Bilan eau "//clnsurf(nsrf),"kg/(m2*s)")
771  if (iflag_pbl>1 .and. lev_files(iff).gt.10 ) then
772 CALL histdef2d(iff,o_tke_srf(nsrf)%flag,o_tke_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
773   type_ecri(1) = 't_max(X)'
774   type_ecri(2) = 't_max(X)'
775   type_ecri(3) = 't_max(X)'
776   type_ecri(4) = 't_max(X)'
777   type_ecri(5) = 't_max(X)'
778 CALL histdef2d(iff,o_tke_max_srf(nsrf)%flag,o_tke_max_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-")
779   type_ecri(:) = type_ecri_files(:)
780  endif
781 CALL histdef2d(iff,o_albe_srf(nsrf)%flag,o_albe_srf(nsrf)%name,"Albedo surf. "//clnsurf(nsrf),"-")
782 CALL histdef2d(iff,o_rugs_srf(nsrf)%flag,o_rugs_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2")
783 CALL histdef2d(iff,o_ages_srf(nsrf)%flag,o_ages_srf(nsrf)%name,"Snow age", "day")
784     END DO
785
786 IF (ok_ade) THEN
787  CALL histdef2d(iff,o_topswad%flag,o_topswad%name, "ADE at TOA", "W/m2")
788  CALL histdef2d(iff,o_solswad%flag,o_solswad%name, "ADE at SRF", "W/m2")
789 ENDIF
790
791 IF (ok_aie) THEN
792  CALL histdef2d(iff,o_topswai%flag,o_topswai%name, "AIE at TOA", "W/m2")
793  CALL histdef2d(iff,o_solswai%flag,o_solswai%name, "AIE at SFR", "W/m2")
794 ENDIF
795
796
797 CALL histdef2d(iff,o_albs%flag,o_albs%name, "Surface albedo", "-")
798 CALL histdef2d(iff,o_albslw%flag,o_albslw%name, "Surface albedo LW", "-")
799 CALL histdef2d(iff,o_cdrm%flag,o_cdrm%name, "Momentum drag coef.", "-")
800 CALL histdef2d(iff,o_cdrh%flag,o_cdrh%name, "Heat drag coef.", "-" )
801 CALL histdef2d(iff,o_cldl%flag,o_cldl%name, "Low-level cloudiness", "-")
802 CALL histdef2d(iff,o_cldm%flag,o_cldm%name, "Mid-level cloudiness", "-")
803 CALL histdef2d(iff,o_cldh%flag,o_cldh%name, "High-level cloudiness", "-")
804 CALL histdef2d(iff,o_cldt%flag,o_cldt%name, "Total cloudiness", "%")
805 CALL histdef2d(iff,o_cldq%flag,o_cldq%name, "Cloud liquid water path", "kg/m2")
806 CALL histdef2d(iff,o_lwp%flag,o_lwp%name, "Cloud water path", "kg/m2")
807 CALL histdef2d(iff,o_iwp%flag,o_iwp%name, "Cloud ice water path", "kg/m2" )
808 CALL histdef2d(iff,o_ue%flag,o_ue%name, "Zonal energy transport", "-")
809 CALL histdef2d(iff,o_ve%flag,o_ve%name, "Merid energy transport", "-")
810 CALL histdef2d(iff,o_uq%flag,o_uq%name, "Zonal humidity transport", "-")
811 CALL histdef2d(iff,o_vq%flag,o_vq%name, "Merid humidity transport", "-")
812
813     IF(iflag_con.GE.3) THEN ! sb
814 CALL histdef2d(iff,o_cape%flag,o_cape%name, "Conv avlbl pot ener", "J/kg")
815 CALL histdef2d(iff,o_pbase%flag,o_pbase%name, "Cld base pressure", "mb")
816 CALL histdef2d(iff,o_ptop%flag,o_ptop%name, "Cld top pressure", "mb")
817 CALL histdef2d(iff,o_fbase%flag,o_fbase%name, "Cld base mass flux", "kg/m2/s")
818 CALL histdef2d(iff,o_prw%flag,o_prw%name, "Precipitable water", "kg/m2")
819   type_ecri(1) = 't_max(X)'
820   type_ecri(2) = 't_max(X)'
821   type_ecri(3) = 't_max(X)'
822   type_ecri(4) = 't_max(X)'
823   type_ecri(5) = 't_max(X)'
824 CALL histdef2d(iff,o_cape_max%flag,o_cape_max%name, "CAPE max.", "J/kg")
825   type_ecri(:) = type_ecri_files(:)
826 CALL histdef3d(iff,o_upwd%flag,o_upwd%name, "saturated updraft", "kg/m2/s")
827 CALL histdef3d(iff,o_Ma%flag,o_Ma%name, "undilute adiab updraft", "kg/m2/s")
828 CALL histdef3d(iff,o_dnwd%flag,o_dnwd%name, "saturated downdraft", "kg/m2/s")
829 CALL histdef3d(iff,o_dnwd0%flag,o_dnwd0%name, "unsat. downdraft", "kg/m2/s")
830     ENDIF !iflag_con .GE. 3
831
832 CALL histdef2d(iff,o_s_pblh%flag,o_s_pblh%name, "Boundary Layer Height", "m")
833 CALL histdef2d(iff,o_s_pblt%flag,o_s_pblt%name, "t at Boundary Layer Height", "K")
834 CALL histdef2d(iff,o_s_lcl%flag,o_s_lcl%name, "Condensation level", "m")
835 CALL histdef2d(iff,o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" )
836 CALL histdef2d(iff,o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2")
837 CALL histdef2d(iff,o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K")
838 CALL histdef2d(iff,o_s_therm%flag,o_s_therm%name, "Exces du thermique", "K")
839 CALL histdef2d(iff,o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2")
840 CALL histdef2d(iff,o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2")
841 CALL histdef2d(iff,o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m")
842
843! Champs interpolles sur des niveaux de pression
844
845   type_ecri(1) = 'inst(X)'
846   type_ecri(2) = 'inst(X)'
847   type_ecri(3) = 'inst(X)'
848   type_ecri(4) = 'inst(X)'
849   type_ecri(5) = 'inst(X)'
850
851! Attention a reverifier
852
853        ilev=0       
854        DO k=1, nlevSTD
855!     IF(k.GE.2.AND.k.LE.12) bb2=clevSTD(k)
856     bb2=clevSTD(k)
857     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
858      ilev=ilev+1
859      print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name
860 CALL histdef2d(iff,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name,"Zonal wind "//bb2//"mb", "m/s")
861 CALL histdef2d(iff,o_vSTDlevs(ilev)%flag,o_vSTDlevs(ilev)%name,"Meridional wind "//bb2//"mb", "m/s")
862 CALL histdef2d(iff,o_wSTDlevs(ilev)%flag,o_wSTDlevs(ilev)%name,"Vertical wind "//bb2//"mb", "Pa/s")
863 CALL histdef2d(iff,o_phiSTDlevs(ilev)%flag,o_phiSTDlevs(ilev)%name,"Geopotential "//bb2//"mb", "m")
864 CALL histdef2d(iff,o_qSTDlevs(ilev)%flag,o_qSTDlevs(ilev)%name,"Specific humidity "//bb2//"mb", "kg/kg" )
865 CALL histdef2d(iff,o_tSTDlevs(ilev)%flag,o_tSTDlevs(ilev)%name,"Temperature "//bb2//"mb", "K")
866     ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10")
867       ENDDO
868   type_ecri(:) = type_ecri_files(:)
869
870 CALL histdef2d(iff,o_t_oce_sic%flag,o_t_oce_sic%name, "Temp mixte oce-sic", "K")
871
872 IF (type_ocean=='slab') &
873     CALL histdef2d(iff,o_slab_bils%flag, o_slab_bils%name,"Bilan au sol sur ocean slab", "W/m2")
874
875! Couplage conv-CL
876 IF (iflag_con.GE.3) THEN
877    IF (iflag_coupl.EQ.1) THEN
878 CALL histdef2d(iff,o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2")
879 CALL histdef2d(iff,o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2")
880    ENDIF
881 ENDIF !(iflag_con.GE.3)
882
883 CALL histdef2d(iff,o_weakinv%flag,o_weakinv%name, "Weak inversion", "-")
884 CALL histdef2d(iff,o_dthmin%flag,o_dthmin%name, "dTheta mini", "K/m")
885 CALL histdef2d(iff,o_rh2m%flag,o_rh2m%name, "Relative humidity at 2m", "%" )
886 CALL histdef2d(iff,o_qsat2m%flag,o_qsat2m%name, "Saturant humidity at 2m", "%")
887 CALL histdef2d(iff,o_tpot%flag,o_tpot%name, "Surface air potential temperature", "K")
888 CALL histdef2d(iff,o_tpote%flag,o_tpote%name, "Surface air equivalent potential temperature", "K")
889 CALL histdef2d(iff,o_SWnetOR%flag,o_SWnetOR%name, "Sfce net SW radiation OR", "W/m2")
890 CALL histdef2d(iff,o_SWdownOR%flag,o_SWdownOR%name, "Sfce incident SW radiation OR", "W/m2")
891 CALL histdef2d(iff,o_LWdownOR%flag,o_LWdownOR%name, "Sfce incident LW radiation OR", "W/m2")
892 CALL histdef2d(iff,o_snowl%flag,o_snowl%name, "Solid Large-scale Precip.", "kg/(m2*s)")
893
894 CALL histdef2d(iff,o_solldown%flag,o_solldown%name, "Down. IR rad. at surface", "W/m2")
895 CALL histdef2d(iff,o_dtsvdfo%flag,o_dtsvdfo%name, "Boundary-layer dTs(o)", "K/s")
896 CALL histdef2d(iff,o_dtsvdft%flag,o_dtsvdft%name, "Boundary-layer dTs(t)", "K/s")
897 CALL histdef2d(iff,o_dtsvdfg%flag,o_dtsvdfg%name, "Boundary-layer dTs(g)", "K/s")
898 CALL histdef2d(iff,o_dtsvdfi%flag,o_dtsvdfi%name, "Boundary-layer dTs(g)", "K/s")
899 CALL histdef2d(iff,o_rugs%flag,o_rugs%name, "rugosity", "-" )
900
901! Champs 3D:
902 CALL histdef3d(iff,o_lwcon%flag,o_lwcon%name, "Cloud liquid water content", "kg/kg")
903 CALL histdef3d(iff,o_iwcon%flag,o_iwcon%name, "Cloud ice water content", "kg/kg")
904 CALL histdef3d(iff,o_temp%flag,o_temp%name, "Air temperature", "K" )
905 CALL histdef3d(iff,o_theta%flag,o_theta%name, "Potential air temperature", "K" )
906 CALL histdef3d(iff,o_ovap%flag,o_ovap%name, "Specific humidity + dqphy", "kg/kg" )
907 CALL histdef3d(iff,o_ovapinit%flag,o_ovapinit%name, "Specific humidity", "kg/kg" )
908 CALL histdef3d(iff,o_geop%flag,o_geop%name, "Geopotential height", "m2/s2")
909 CALL histdef3d(iff,o_vitu%flag,o_vitu%name, "Zonal wind", "m/s" )
910 CALL histdef3d(iff,o_vitv%flag,o_vitv%name, "Meridional wind", "m/s" )
911 CALL histdef3d(iff,o_vitw%flag,o_vitw%name, "Vertical wind", "Pa/s" )
912 CALL histdef3d(iff,o_pres%flag,o_pres%name, "Air pressure", "Pa" )
913 CALL histdef3d(iff,o_rneb%flag,o_rneb%name, "Cloud fraction", "-")
914 CALL histdef3d(iff,o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-")
915 CALL histdef3d(iff,o_rhum%flag,o_rhum%name, "Relative humidity", "-")
916 CALL histdef3d(iff,o_ozone%flag,o_ozone%name, "Ozone mole fraction", "-")
917 CALL histdef3d(iff,o_dtphy%flag,o_dtphy%name, "Physics dT", "K/s")
918 CALL histdef3d(iff,o_dqphy%flag,o_dqphy%name, "Physics dQ", "(kg/kg)/s")
919 CALL histdef3d(iff,o_cldtau%flag,o_cldtau%name, "Cloud optical thickness", "1")
920 CALL histdef3d(iff,o_cldemi%flag,o_cldemi%name, "Cloud optical emissivity", "1")
921!IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl
922! CALL histdef3d(iff,o_pr_con_l%flag,o_pmflxr%name, "Convective precipitation lic", " ")
923! CALL histdef3d(iff,o_pr_con_i%flag,o_pmflxs%name, "Convective precipitation ice", " ")
924! CALL histdef3d(iff,o_pr_lsc_l%flag,o_prfl%name, "Large scale precipitation lic", " ")
925! CALL histdef3d(iff,o_pr_lsc_i%flag,o_psfl%name, "Large scale precipitation ice", " ")
926
927!FH Sorties pour la couche limite
928     if (iflag_pbl>1) then
929 CALL histdef3d(iff,o_tke%flag,o_tke%name, "TKE", "m2/s2")
930   type_ecri(1) = 't_max(X)'
931   type_ecri(2) = 't_max(X)'
932   type_ecri(3) = 't_max(X)'
933   type_ecri(4) = 't_max(X)'
934   type_ecri(5) = 't_max(X)'
935 CALL histdef3d(iff,o_tke_max%flag,o_tke_max%name, "TKE max", "m2/s2")
936   type_ecri(:) = type_ecri_files(:)
937     endif
938
939 CALL histdef3d(iff,o_kz%flag,o_kz%name, "Kz melange", "m2/s")
940   type_ecri(1) = 't_max(X)'
941   type_ecri(2) = 't_max(X)'
942   type_ecri(3) = 't_max(X)'
943   type_ecri(4) = 't_max(X)'
944   type_ecri(5) = 't_max(X)'
945 CALL histdef3d(iff,o_kz_max%flag,o_kz_max%name, "Kz melange max", "m2/s" )
946   type_ecri(:) = type_ecri_files(:)
947 CALL histdef3d(iff,o_clwcon%flag,o_clwcon%name, "Convective Cloud Liquid water content", "kg/kg")
948 CALL histdef3d(iff,o_dtdyn%flag,o_dtdyn%name, "Dynamics dT", "K/s")
949 CALL histdef3d(iff,o_dqdyn%flag,o_dqdyn%name, "Dynamics dQ", "(kg/kg)/s")
950 CALL histdef3d(iff,o_dudyn%flag,o_dudyn%name, "Dynamics dU", "m/s2")
951 CALL histdef3d(iff,o_dvdyn%flag,o_dvdyn%name, "Dynamics dV", "m/s2")
952 CALL histdef3d(iff,o_dtcon%flag,o_dtcon%name, "Convection dT", "K/s")
953 CALL histdef3d(iff,o_ducon%flag,o_ducon%name, "Convection du", "m/s2")
954 CALL histdef3d(iff,o_dqcon%flag,o_dqcon%name, "Convection dQ", "(kg/kg)/s")
955
956! Wakes
957 IF(iflag_con.EQ.3) THEN
958 IF (iflag_wake == 1) THEN
959   CALL histdef2d(iff,o_ale_wk%flag,o_ale_wk%name, "ALE WK", "m2/s2")
960   CALL histdef2d(iff,o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2")
961   CALL histdef2d(iff,o_ale%flag,o_ale%name, "ALE", "m2/s2")
962   CALL histdef2d(iff,o_alp%flag,o_alp%name, "ALP", "W/m2")
963   CALL histdef2d(iff,o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2")
964   CALL histdef2d(iff,o_wape%flag,o_WAPE%name, "WAPE", "m2/s2")
965   CALL histdef2d(iff,o_wake_h%flag,o_wake_h%name, "wake_h", "-")
966   CALL histdef2d(iff,o_wake_s%flag,o_wake_s%name, "wake_s", "-")
967   CALL histdef3d(iff,o_dtwak%flag,o_dtwak%name, "Wake dT", "K/s")
968   CALL histdef3d(iff,o_dqwak%flag,o_dqwak%name, "Wake dQ", "(kg/kg)/s")
969   CALL histdef3d(iff,o_wake_deltat%flag,o_wake_deltat%name, "wake_deltat", " ")
970   CALL histdef3d(iff,o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ")
971   CALL histdef3d(iff,o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ")
972 ENDIF
973   CALL histdef3d(iff,o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-")
974   CALL histdef3d(iff,o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-")
975   CALL histdef3d(iff,o_fqd%flag,o_fqd%name,"tend vap eau due aux descentes precip", "-")
976 ENDIF !(iflag_con.EQ.3)
977
978 CALL histdef3d(iff,o_dtlsc%flag,o_dtlsc%name, "Condensation dT", "K/s")
979 CALL histdef3d(iff,o_dtlschr%flag,o_dtlschr%name,"Large-scale condensational heating rate","K/s")
980 CALL histdef3d(iff,o_dqlsc%flag,o_dqlsc%name, "Condensation dQ", "(kg/kg)/s")
981 CALL histdef3d(iff,o_dtvdf%flag,o_dtvdf%name, "Boundary-layer dT", "K/s")
982 CALL histdef3d(iff,o_dqvdf%flag,o_dqvdf%name, "Boundary-layer dQ", "(kg/kg)/s")
983 CALL histdef3d(iff,o_dteva%flag,o_dteva%name, "Reevaporation dT", "K/s")
984 CALL histdef3d(iff,o_dqeva%flag,o_dqeva%name, "Reevaporation dQ", "(kg/kg)/s")
985 CALL histdef3d(iff,o_ptconv%flag,o_ptconv%name, "POINTS CONVECTIFS", " ")
986 CALL histdef3d(iff,o_ratqs%flag,o_ratqs%name, "RATQS", " ")
987 CALL histdef3d(iff,o_dtthe%flag,o_dtthe%name, "Dry adjust. dT", "K/s")
988
989if(iflag_thermals.gt.1) THEN
990 CALL histdef3d(iff,o_f_th%flag,o_f_th%name, "Thermal plume mass flux", "K/s")
991 CALL histdef3d(iff,o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s")
992 CALL histdef3d(iff,o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s")
993 CALL histdef3d(iff,o_lambda_th%flag,o_lambda_th%name,"Thermal plume vertical velocity","m/s")
994 CALL histdef3d(iff,o_q_th%flag,o_q_th%name, "Thermal plume total humidity", "kg/kg")
995 CALL histdef3d(iff,o_a_th%flag,o_a_th%name, "Thermal plume fraction", "")
996 CALL histdef3d(iff,o_d_th%flag,o_d_th%name, "Thermal plume detrainment", "K/s")
997endif !iflag_thermals.gt.1
998 CALL histdef2d(iff,o_f0_th%flag,o_f0_th%name, "Thermal closure mass flux", "K/s")
999 CALL histdef2d(iff,o_zmax_th%flag,o_zmax_th%name, "Thermal plume height", "K/s")
1000 CALL histdef3d(iff,o_dqthe%flag,o_dqthe%name, "Dry adjust. dQ", "(kg/kg)/s")
1001 CALL histdef3d(iff,o_dtajs%flag,o_dtajs%name, "Dry adjust. dT", "K/s")
1002 CALL histdef3d(iff,o_dqajs%flag,o_dqajs%name, "Dry adjust. dQ", "(kg/kg)/s")
1003 CALL histdef3d(iff,o_dtswr%flag,o_dtswr%name, "SW radiation dT", "K/s")
1004 CALL histdef3d(iff,o_dtsw0%flag,o_dtsw0%name, "CS SW radiation dT", "K/s")
1005 CALL histdef3d(iff,o_dtlwr%flag,o_dtlwr%name, "LW radiation dT", "K/s")
1006 CALL histdef3d(iff,o_dtlw0%flag,o_dtlw0%name, "CS LW radiation dT", "K/s")
1007 CALL histdef3d(iff,o_dtec%flag,o_dtec%name, "Cinetic dissip dT", "K/s")
1008 CALL histdef3d(iff,o_duvdf%flag,o_duvdf%name, "Boundary-layer dU", "m/s2")
1009 CALL histdef3d(iff,o_dvvdf%flag,o_dvvdf%name, "Boundary-layer dV", "m/s2")
1010
1011     IF (ok_orodr) THEN
1012 CALL histdef3d(iff,o_duoro%flag,o_duoro%name, "Orography dU", "m/s2")
1013 CALL histdef3d(iff,o_dvoro%flag,o_dvoro%name, "Orography dV", "m/s2")
1014     ENDIF
1015
1016     IF (ok_orolf) THEN
1017 CALL histdef3d(iff,o_dulif%flag,o_dulif%name, "Orography dU", "m/s2")
1018 CALL histdef3d(iff,o_dvlif%flag,o_dvlif%name, "Orography dV", "m/s2")
1019     ENDIF
1020
1021      if (nqtot>=3) THEN
1022!Attention    DO iq=3,nqtot
1023    DO iq=3,4 
1024       iiq=niadv(iq)
1025! CALL histdef3d (iff, o_trac%flag,'o_'//tnom(iq)%name,ttext(iiq), "-" )
1026  CALL histdef3d (iff, o_trac(iq-2)%flag,o_trac(iq-2)%name,ttext(iiq), "-" )
1027    ENDDO
1028      endif
1029
1030        CALL histend(nid_files(iff))
1031
1032         ndex2d = 0
1033         ndex3d = 0
1034
1035         ENDIF ! clef_files
1036
1037         ENDDO !  iff
1038     print*,'Fin phys_output_mod.F90'
1039      end subroutine phys_output_open
1040
1041      SUBROUTINE histdef2d (iff,flag_var,nomvar,titrevar,unitvar)
1042     
1043       use ioipsl
1044       USE dimphy
1045       USE mod_phys_lmdz_para
1046
1047       IMPLICIT NONE
1048       
1049       include "dimensions.h"
1050       include "temps.h"
1051       include "indicesol.h"
1052       include "clesphys.h"
1053
1054       integer                          :: iff
1055       integer, dimension(nfiles)       :: flag_var
1056       character(len=20)                 :: nomvar
1057       character(len=*)                 :: titrevar
1058       character(len=*)                 :: unitvar
1059
1060       real zstophym
1061
1062       if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
1063         zstophym=zoutm(iff)
1064       else
1065         zstophym=zdtime
1066       endif
1067
1068! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
1069       call conf_physoutputs(nomvar,flag_var)
1070       
1071       if ( flag_var(iff)<=lev_files(iff) ) then
1072 call histdef (nid_files(iff),nomvar,titrevar,unitvar, &
1073               iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &
1074               type_ecri(iff), zstophym,zoutm(iff))               
1075       endif                     
1076      end subroutine histdef2d
1077
1078      SUBROUTINE histdef3d (iff,flag_var,nomvar,titrevar,unitvar)
1079
1080       use ioipsl
1081       USE dimphy
1082       USE mod_phys_lmdz_para
1083
1084       IMPLICIT NONE
1085
1086       include "dimensions.h"
1087       include "temps.h"
1088       include "indicesol.h"
1089       include "clesphys.h"
1090
1091       integer                          :: iff
1092       integer, dimension(nfiles)       :: flag_var
1093       character(len=20)                 :: nomvar
1094       character(len=*)                 :: titrevar
1095       character(len=*)                 :: unitvar
1096
1097       real zstophym
1098
1099! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def
1100       call conf_physoutputs(nomvar,flag_var)
1101
1102       if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then
1103         zstophym=zoutm(iff)
1104       else
1105         zstophym=zdtime
1106       endif
1107
1108       if ( flag_var(iff)<=lev_files(iff) ) then
1109          call histdef (nid_files(iff), nomvar, titrevar, unitvar, &
1110               iim, jj_nb, nhorim(iff), klev, levmin(iff), &
1111               levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), &
1112               zstophym, zoutm(iff))
1113       endif
1114      end subroutine histdef3d
1115
1116      SUBROUTINE conf_physoutputs(nam_var,flag_var)
1117!!! Lecture des noms et niveau de sortie des variables dans output.def
1118!   en utilisant les routines getin de IOIPSL 
1119       use ioipsl
1120
1121       IMPLICIT NONE
1122
1123       include 'iniprint.h'
1124
1125       character(len=20)                :: nam_var
1126       integer, dimension(nfiles)      :: flag_var
1127
1128        IF(prt_level>10) WRITE(lunout,*)'Avant getin: nam_var flag_var ',nam_var,flag_var(:)
1129        call getin('flag_'//nam_var,flag_var)
1130        call getin('name_'//nam_var,nam_var)
1131        IF(prt_level>10) WRITE(lunout,*)'Apres getin: nam_var flag_var ',nam_var,flag_var(:)
1132
1133      END SUBROUTINE conf_physoutputs
1134
1135      SUBROUTINE convers_timesteps(str,timestep)
1136
1137        use ioipsl
1138
1139        IMPLICIT NONE
1140
1141        character(len=20)   :: str
1142        character(len=10)   :: type
1143        integer             :: ipos,il
1144        real                :: ttt,xxx,timestep,dayseconde
1145        parameter (dayseconde=86400.)
1146        include "temps.h"
1147        include "comconst.h"
1148
1149        ipos=scan(str,'0123456789.',.true.)
1150
1151        il=len_trim(str)
1152        print*,ipos,il
1153        read(str(1:ipos),*) ttt
1154        print*,ttt
1155        type=str(ipos+1:il)
1156
1157
1158        if ( il == ipos ) then
1159        type='day'
1160        endif
1161
1162        if ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde
1163        if ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then
1164           print*,'annee_ref,day_ref mon_len',annee_ref,day_ref,ioget_mon_len(annee_ref,day_ref)
1165           timestep = ttt * dayseconde * ioget_mon_len(annee_ref,day_ref)
1166        endif
1167        if ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.
1168        if ( type == 'mn'.or.type == 'minutes'  ) timestep = ttt * 60.
1169        if ( type == 's'.or.type == 'sec'.or.type == 'secondes'   ) timestep = ttt
1170        if ( type == 'TS' ) timestep = dtphys
1171
1172        print*,'type =      ',type
1173        print*,'nb j/h/m =  ',ttt
1174        print*,'timestep(s)=',timestep
1175
1176        END SUBROUTINE convers_timesteps
1177
1178END MODULE phys_output_mod
1179
Note: See TracBrowser for help on using the repository browser.