source: LMDZ5/branches/AI-cosp/libf/phylmd/cosp/cosp_output_mod.F90 @ 3717

Last change on this file since 3717 was 2428, checked in by idelkadi, 9 years ago

Mise a jour du simulateur COSP (passage de la version v3.2 a la version v1.4) :

  • mise a jour des sources pour ISCCP, CALIPSO et PARASOL
  • prise en compte des changements de phases pour les nuages (Calipso)
  • rajout de plusieurs diagnostiques (fraction nuageuse en fonction de la temperature, ...)

http://lmdz.lmd.jussieu.fr/Members/aidelkadi/cosp

File size: 20.1 KB
Line 
1! A.Idelkadi sept 2013 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2!! Module pour declarer et initialiser les parametres de controle des fichiers de sorties et des champs a sortir
3!! La routine cosp_output_open (appelee 1 seule fois dans phy_cosp.F90) permet :
4!! de creer les fichiers avec leurs grilles horizontales et verticales
5!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
6  MODULE cosp_output_mod
7
8  USE MOD_COSP_CONSTANTS
9  USE MOD_COSP_TYPES
10  use MOD_COSP_Modis_Simulator, only : cosp_modis
11
12! cosp_output_mod
13      INTEGER, PRIVATE             :: i
14!!!!!!! Controle des fichier de sorties Cosp !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
15      LOGICAL, DIMENSION(3), SAVE  :: cosp_outfilekeys
16      INTEGER, DIMENSION(3), SAVE  :: cosp_nidfiles
17!$OMP THREADPRIVATE(cosp_outfilekeys, cosp_nidfiles)
18      INTEGER, DIMENSION(3), SAVE  :: nhoricosp,nvert,nvertmcosp,nvertcol,nvertisccp,nvertp,nverttemp,nvertmisr
19      REAL, DIMENSION(3), SAVE                :: zoutm_cosp
20!$OMP THREADPRIVATE(nhoricosp, nvert, nvertmcosp, nvertcol, nvertisccp, nvertp, zoutm_cosp, nverttemp, nvertmisr)
21      REAL, SAVE                   :: zdtimemoy_cosp
22!$OMP THREADPRIVATE(zdtimemoy_cosp)
23      CHARACTER(LEN=20), DIMENSION(3), SAVE  :: cosp_outfiletypes
24      CHARACTER(LEN=20), DIMENSION(3), SAVE  :: cosp_outfilenames
25      REAL, DIMENSION(3), SAVE               :: cosp_ecritfiles
26!$OMP THREADPRIVATE(cosp_outfiletypes, cosp_outfilenames, cosp_ecritfiles)
27
28!!!!  Controle des variables a sortir dans les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
29  TYPE ctrl_outcosp
30     LOGICAL,DIMENSION(3)                 :: cles             !!! Sortir ou non le champs
31     CHARACTER(len=20)                    :: name       
32     CHARACTER(len=150)                   :: description      !!! Nom
33     CHARACTER(len=20)                    :: unit             !!! Unite
34     CHARACTER(len=20),DIMENSION(3)  :: cosp_typeecrit        !!! Operation (ave, inst, ...)
35  END TYPE ctrl_outcosp
36
37! CALIPSO vars
38  TYPE(ctrl_outcosp), SAVE :: o_cllcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
39         "cllcalipso", "Lidar Low-level Cloud Fraction", "%", (/ ('', i=1, 3) /))                                   
40  TYPE(ctrl_outcosp), SAVE :: o_clmcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
41         "clmcalipso", "Lidar Mid-level Cloud Fraction", "%", (/ ('', i=1, 3) /))
42  TYPE(ctrl_outcosp), SAVE :: o_clhcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
43         "clhcalipso", "Lidar Hight-level Cloud Fraction", "%", (/ ('', i=1, 3) /))
44  TYPE(ctrl_outcosp), SAVE :: o_cltcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
45         "cltcalipso", "Lidar Total Cloud Fraction", "%", (/ ('', i=1, 3) /))
46  TYPE(ctrl_outcosp), SAVE :: o_clcalipso = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
47         "clcalipso", "Lidar Cloud Fraction (532 nm)", "%", (/ ('', i=1, 3) /))
48  TYPE(ctrl_outcosp), SAVE :: o_cfad_lidarsr532 = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
49         "cfad_lidarsr532", "Lidar Scattering Ratio CFAD (532 nm)", "1", (/ ('', i=1, 3) /))   
50  TYPE(ctrl_outcosp), SAVE :: o_parasol_refl = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
51         "parasol_refl", "PARASOL-like mono-directional reflectance","1", (/ ('', i=1, 3) /))
52  TYPE(ctrl_outcosp), SAVE :: o_parasol_crefl = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &             
53         "parasol_crefl", "PARASOL-like mono-directional reflectance (integral)","1", (/ ('', i=1, 3) /))                 
54  TYPE(ctrl_outcosp), SAVE :: o_Ncrefl = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
55         "Ncrefl", "Nb PARASOL-like mono-directional reflectance (integral)","1", (/ ('', i=1, 3) /))
56  TYPE(ctrl_outcosp), SAVE :: o_atb532 = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
57         "atb532", "Lidar Attenuated Total Backscatter (532 nm)","1", (/ ('', i=1, 3) /))
58  TYPE(ctrl_outcosp), SAVE :: o_beta_mol532 = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
59         "beta_mol532", "Lidar Molecular Backscatter (532 nm)","m-1 sr-1", (/ ('', i=1, 3) /))
60!! AI  11 2015
61  TYPE(ctrl_outcosp), SAVE :: o_cllcalipsoice = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
62         "cllcalipsoice", "CALIPSO Ice-Phase Low Level Cloud Fraction", "%", (/ ('', i=1, 3) /)) 
63  TYPE(ctrl_outcosp), SAVE :: o_cllcalipsoliq = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
64         "cllcalipsoliq", "CALIPSO Liq-Phase Low Level Cloud Fraction", "%", (/ ('', i=1, 3) /))
65  TYPE(ctrl_outcosp), SAVE :: o_clmcalipsoice = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
66         "clmcalipsoice", "CALIPSO Ice-Phase Mid Level Cloud Fraction", "%", (/ ('', i=1, 3) /))
67  TYPE(ctrl_outcosp), SAVE :: o_clmcalipsoliq = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
68         "clmcalipsoliq", "CALIPSO Liq-Phase Mid Level Cloud Fraction", "%", (/ ('', i=1, 3) /))                 
69  TYPE(ctrl_outcosp), SAVE :: o_clhcalipsoice = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
70         "clhcalipsoice", "CALIPSO Ice-Phase High Level Cloud Fraction", "%", (/ ('', i=1, 3) /)) 
71  TYPE(ctrl_outcosp), SAVE :: o_clhcalipsoliq = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
72         "clhcalipsoliq", "CALIPSO Liq-Phase High Level Cloud Fraction", "%", (/ ('', i=1, 3) /))
73  TYPE(ctrl_outcosp), SAVE :: o_cltcalipsoice = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
74         "cltcalipsoice", "CALIPSO Ice-Phase Tot Level Cloud Fraction", "%", (/ ('', i=1, 3) /))
75  TYPE(ctrl_outcosp), SAVE :: o_cltcalipsoliq = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
76         "cltcalipsoliq", "CALIPSO Liq-Phase Tot Level Cloud Fraction", "%", (/ ('', i=1, 3) /))                 
77  TYPE(ctrl_outcosp), SAVE :: o_cllcalipsoun = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
78         "cllcalipsoun", "CALIPSO Undefined-Phase Low Level Cloud Fraction", "%", (/ ('', i=1, 3) /)) 
79  TYPE(ctrl_outcosp), SAVE :: o_clmcalipsoun = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
80         "clmcalipsoun", "CALIPSO Undefined-Phase Mid Level Cloud Fraction", "%", (/ ('', i=1, 3) /))
81  TYPE(ctrl_outcosp), SAVE :: o_clhcalipsoun = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
82         "clhcalipsoun", "CALIPSO Undefined-Phase High Level Cloud Fraction", "%", (/ ('', i=1, 3) /))
83  TYPE(ctrl_outcosp), SAVE :: o_cltcalipsoun = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
84         "cltcalipsoun", "CALIPSO Undefined-Phase Tot Level Cloud Fraction", "%", (/ ('', i=1, 3) /))
85  TYPE(ctrl_outcosp), SAVE :: o_clcalipsoice = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
86         "clcalipsoice", "Lidar Ice-Phase Cloud Fraction", "%", (/ ('', i=1, 3) /))
87  TYPE(ctrl_outcosp), SAVE :: o_clcalipsoliq = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
88         "clcalipsoliq", "Lidar Liq-Phase Cloud Fraction", "%", (/ ('', i=1, 3) /))
89  TYPE(ctrl_outcosp), SAVE :: o_clcalipsoun = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
90         "clcalipsoun", "Lidar Undef-Phase Cloud Fraction", "%", (/ ('', i=1, 3) /))     
91  TYPE(ctrl_outcosp), SAVE :: o_clcalipsotmpice = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
92         "clcalipsotmpice", "Lidar Ice-Phase Cloud Fraction", "%", (/ ('', i=1, 3) /))
93  TYPE(ctrl_outcosp), SAVE :: o_clcalipsotmpliq = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
94         "clcalipsotmpliq", "Lidar Liq-Phase Cloud Fraction", "%", (/ ('', i=1, 3) /))
95  TYPE(ctrl_outcosp), SAVE :: o_clcalipsotmpun = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
96         "clcalipsotmpun", "Lidar Undef-Phase Cloud Fraction", "%", (/ ('', i=1, 3) /))
97  TYPE(ctrl_outcosp), SAVE :: o_clcalipsotmp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
98         "clcalipsotmp", "Lidar Cloud Fraction", "%", (/ ('', i=1, 3) /))
99
100! Radar Cloudsat
101  TYPE(ctrl_outcosp), SAVE :: o_cfadDbze94 = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
102         "cfadDbze94", "CloudSat Radar Reflectivity CFAD", "%", (/ ('', i=1, 3) /))
103  TYPE(ctrl_outcosp), SAVE :: o_dbze94 = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
104         "dbze94", "CloudSat Radar Reflectivity", "%", (/ ('', i=1, 3) /))
105
106! Calipso + Cloudsat
107  TYPE(ctrl_outcosp), SAVE :: o_clcalipso2 = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
108         "clcalipso2", "CALIPSO Cloud Fraction Undetected by CloudSat", "1", (/ ('', i=1, 3) /))
109
110! ISCCP vars
111  TYPE(ctrl_outcosp), SAVE :: o_sunlit = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
112         "sunlit", "1 for day points, 0 for nightime","1",(/ ('', i=1, 3) /))                   
113  TYPE(ctrl_outcosp), SAVE :: o_clisccp2 = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
114         "clisccp2", "Cloud Fraction as Calculated by the ISCCP Simulator","1", (/ ('', i=1, 3) /))
115  TYPE(ctrl_outcosp), SAVE :: o_boxtauisccp = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
116         "boxtauisccp", "Optical Depth in Each Column as Calculated by the ISCCP Simulator","1", (/ ('', i=1, 3) /))
117  TYPE(ctrl_outcosp), SAVE :: o_boxptopisccp = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
118         "boxptopisccp", "Cloud Top Pressure in Each Column as Calculated by the ISCCP Simulator","Pa", (/ ('', i=1, 3) /))
119  TYPE(ctrl_outcosp), SAVE :: o_tclisccp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
120          "tclisccp", "Total Cloud Fraction as Calculated by the ISCCP Simulator", "1", (/ ('', i=1, 3) /))
121  TYPE(ctrl_outcosp), SAVE :: o_ctpisccp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
122          "ctpisccp", "Mean Cloud Top Pressure as Calculated by the ISCCP Simulator", "Pa", (/ ('', i=1, 3) /))
123  TYPE(ctrl_outcosp), SAVE :: o_tauisccp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
124          "tauisccp", "Optical Depth as Calculated by the ISCCP Simulator", "1", (/ ('', i=1, 3) /))
125  TYPE(ctrl_outcosp), SAVE :: o_albisccp = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
126          "albisccp", "Mean Cloud Albedo as Calculated by the ISCCP Simulator", "1", (/ ('', i=1, 3) /))
127  TYPE(ctrl_outcosp), SAVE :: o_meantbisccp = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
128          "meantbisccp", " Mean all-sky 10.5 micron brightness temperature as calculated &
129           by the ISCCP Simulator","K", (/ ('', i=1, 3) /))
130  TYPE(ctrl_outcosp), SAVE :: o_meantbclrisccp = ctrl_outcosp((/ .FALSE., .FALSE., .FALSE. /), &
131          "meantbclrisccp", "Mean clear-sky 10.5 micron brightness temperature as calculated &
132           by the ISCCP Simulator","K", (/ ('', i=1, 3) /))
133
134! MISR simulator
135  TYPE(ctrl_outcosp), SAVE :: o_clMISR = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
136         "clMISR", "Cloud Fraction as Calculated by the MISR Simulator","1", (/ ('', i=1, 3) /))
137
138! MODIS simulator
139  TYPE(ctrl_outcosp), SAVE :: o_cllmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
140         "cllmodis", "MODIS Low-level Cloud Fraction", "1", (/ ('', i=1, 3) /))                                   
141  TYPE(ctrl_outcosp), SAVE :: o_clmmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
142         "clmmodis", "MODIS Mid-level Cloud Fraction", "1", (/ ('', i=1, 3) /))
143  TYPE(ctrl_outcosp), SAVE :: o_clhmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
144         "clhmodis", "MODIS Hight-level Cloud Fraction", "1", (/ ('', i=1, 3) /))
145  TYPE(ctrl_outcosp), SAVE :: o_cltmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
146         "cltmodis", "MODIS Total Cloud Fraction", "1", (/ ('', i=1, 3) /))
147  TYPE(ctrl_outcosp), SAVE :: o_clwmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
148         "clwmodis", "MODIS Cloud Fraction water mean", "1", (/ ('', i=1, 3) /))
149  TYPE(ctrl_outcosp), SAVE :: o_climodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
150         "climodis", "MODIS Cloud Fraction ice mean", "1", (/ ('', i=1, 3) /)) 
151  TYPE(ctrl_outcosp), SAVE :: o_tautmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
152         "tautmodis", "MODIS Optical_Thickness_Total_Mean", "1", (/ ('', i=1, 3) /))                                   
153  TYPE(ctrl_outcosp), SAVE :: o_tauwmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
154         "tauwmodis", "MODIS Optical_Thickness_Water_Mean", "1", (/ ('', i=1, 3) /))
155  TYPE(ctrl_outcosp), SAVE :: o_tauimodis= ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
156         "tauimodis", "MODIS Optical_Thickness_Ice_Mean", "1", (/ ('', i=1, 3) /))
157  TYPE(ctrl_outcosp), SAVE :: o_tautlogmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
158         "tautlogmodis", "MODIS Optical_Thickness_Total_logMean", "1", (/ ('', i=1, 3) /))                                   
159  TYPE(ctrl_outcosp), SAVE :: o_tauwlogmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
160         "tauwlogmodis", "MODIS Optical_Thickness_Water_logMean", "1", (/ ('', i=1, 3) /))
161  TYPE(ctrl_outcosp), SAVE :: o_tauilogmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
162         "tauilogmodis", "MODIS Optical_Thickness_Ice_logMean", "1", (/ ('', i=1, 3) /))         
163  TYPE(ctrl_outcosp), SAVE :: o_reffclwmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
164         "reffclwmodis", "Modis Cloud_Particle_Size_Water_Mean", "m", (/ ('', i=1, 3) /))               
165  TYPE(ctrl_outcosp), SAVE :: o_reffclimodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
166         "reffclimodis", "Modis Cloud_Particle_Size_Ice_Mean", "m", (/ ('', i=1, 3) /))
167  TYPE(ctrl_outcosp), SAVE :: o_pctmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
168         "pctmodis", "Modis Cloud_Top_Pressure_Total_Mean", "Pa", (/ ('', i=1, 3) /))
169  TYPE(ctrl_outcosp), SAVE :: o_lwpmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
170         "lwpmodis", "Modis Liquid_Water_Path_Mean", "kg m-2", (/ ('', i=1, 3) /))
171  TYPE(ctrl_outcosp), SAVE :: o_iwpmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
172         "iwpmodis", "Modis Ice_Water_Path_Mean", "kg m-2", (/ ('', i=1, 3) /)) 
173  TYPE(ctrl_outcosp), SAVE :: o_clmodis = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
174         "clmodis", "MODIS Cloud Area Fraction", "%", (/ ('', i=1, 3) /))
175
176! Rttovs simulator
177  TYPE(ctrl_outcosp), SAVE :: o_tbrttov = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
178         "tbrttov", "Rttovs Cloud Area Fraction", "%", (/ ('', i=1, 3) /))
179
180! Scops and others
181  TYPE(ctrl_outcosp), SAVE :: o_fracout = ctrl_outcosp((/ .TRUE., .TRUE., .TRUE. /), &
182         "fracout", "Subcolumn output from SCOPS", "%", (/ ('', i=1, 3) /))     
183
184  LOGICAL, SAVE :: cosp_varsdefined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL
185  REAL, SAVE  :: Cosp_fill_value
186!$OMP THREADPRIVATE(Cosp_fill_value)
187 
188
189CONTAINS
190
191!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
192!!!!!!!!! Ouverture des fichier et definition des  axes!!!!!!!!
193  !! histbeg, histvert
194!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
195
196  SUBROUTINE cosp_output_open(Nlevlmdz, Ncolumns, presnivs, dtime, freq_cosp, &
197                              ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, ok_all_xml,  &
198                              ecrit_mth, ecrit_day, ecrit_hf, use_vgrid, vgrid)
199
200
201  USE iophy
202  USE ioipsl
203  USE phys_cal_mod
204  USE time_phylmdz_mod, ONLY: day_ref, annee_ref, day_ini, start_time, itau_phy
205  USE print_control_mod, ONLY: lunout
206
207#ifdef CPP_XIOS
208    ! ug Pour les sorties XIOS
209    USE wxios
210#endif
211
212  IMPLICIT NONE
213
214!!! Variables d'entree
215  integer                  :: Nlevlmdz, Ncolumns      ! Number of levels
216  real,dimension(Nlevlmdz) :: presnivs
217  real                     :: dtime, freq_cosp, ecrit_day, ecrit_hf, ecrit_mth
218  logical                  :: ok_mensuelCOSP, ok_journeCOSP, ok_hfCOSP, use_vgrid, ok_all_xml                   
219  type(cosp_vgrid)   :: vgrid   ! Information on vertical grid of stats
220
221!!! Variables locales
222  integer                  :: idayref, iff, ii
223  real                     :: zjulian,zjulian_start
224  real,dimension(Ncolumns) :: column_ax
225  CHARACTER(LEN=20), DIMENSION(3)  :: chfreq = (/ '1day', '1d', '3h' /)           
226
227!!! Variables d'entree
228
229#ifdef CPP_XIOS
230    ! ug Variables utilisées pour récupérer le calendrier pour xios
231    INTEGER :: x_an, x_mois, x_jour
232    REAL :: x_heure
233    INTEGER :: ini_an, ini_mois, ini_jour
234    REAL :: ini_heure
235#endif
236
237    WRITE(lunout,*) 'Debut cosp_output_mod.F90'
238    print*,'cosp_varsdefined',cosp_varsdefined
239    ! Initialisations (Valeurs par defaut)
240
241    do ii=1,Ncolumns
242      column_ax(ii) = real(ii)
243    enddo
244
245
246    cosp_outfilenames(1) = 'histmthCOSP'
247    cosp_outfilenames(2) = 'histdayCOSP'
248    cosp_outfilenames(3) = 'histhfCOSP'
249
250    cosp_outfiletypes(1) = 'ave(X)'
251    cosp_outfiletypes(2) = 'ave(X)'
252    cosp_outfiletypes(3) = 'ave(X)'
253
254    cosp_outfilekeys(1) = ok_mensuelCOSP
255    cosp_outfilekeys(2) = ok_journeCOSP
256    cosp_outfilekeys(3) = ok_hfCOSP
257
258    cosp_ecritfiles(1) = mth_len*86400.
259    cosp_ecritfiles(2) = 1.*86400.
260    cosp_ecritfiles(3) = 0.125*86400.
261
262! Lecture des parametres dans output.def ou config.def
263
264    CALL getin('cosp_outfilenames',cosp_outfilenames)
265    CALL getin('cosp_outfilekeys',cosp_outfilekeys)
266    CALL getin('cosp_ecritfiles',cosp_ecritfiles)
267    CALL getin('cosp_outfiletypes',cosp_outfiletypes)
268
269    WRITE(lunout,*)'cosp_outfilenames=',cosp_outfilenames
270    WRITE(lunout,*)'cosp_outfilekeys=',cosp_outfilekeys
271    WRITE(lunout,*)'cosp_ecritfiles=',cosp_ecritfiles
272    WRITE(lunout,*)'cosp_outfiletypes=',cosp_outfiletypes
273   
274    idayref = day_ref
275    CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
276    CALL ymds2ju(annee_ref, 1, day_ini, start_time, zjulian_start)
277
278#ifdef CPP_XIOS
279   
280! recuperer la valeur indefine Xios
281!    CALL xios_get_field_attr("clcalipso",default_value=Cosp_fill_value)
282!         Cosp_fill_value=missing_val
283          Cosp_fill_value=0.
284         print*,'Cosp_fill_value=',Cosp_fill_value
285!    if (use_vgrid) then
286!      print*,'vgrid%Nlvgrid, vgrid%z = ',vgrid%Nlvgrid, vgrid%z
287        CALL wxios_add_vaxis("height", vgrid%Nlvgrid, vgrid%z)
288     print*,'wxios_add_vaxis '
289!    else
290!         WRITE(lunout,*) 'wxios_add_vaxis "presnivs", vgrid%Nlvgrid ',vgrid%Nlvgrid
291!        CALL wxios_add_vaxis("presnivs", vgrid%Nlvgrid, presnivs)
292!    endif
293    WRITE(lunout,*) 'wxios_add_vaxis height_mlev, Nlevlmdz ',Nlevlmdz
294    CALL wxios_add_vaxis("height_mlev", Nlevlmdz, vgrid%mz)
295    WRITE(lunout,*) 'wxios_add_vaxis sza, PARASOL_NREFL ',PARASOL_NREFL
296    CALL wxios_add_vaxis("sza", PARASOL_NREFL, PARASOL_SZA)
297    WRITE(lunout,*) 'wxios_add_vaxis pressure2 ',7
298    CALL wxios_add_vaxis("pressure2", 7, ISCCP_PC)
299    WRITE(lunout,*) 'wxios_add_vaxis column ',Ncolumns
300    CALL wxios_add_vaxis("column", Ncolumns, column_ax)
301
302! AI nov 2015
303   CALL wxios_add_vaxis("temp", LIDAR_NTEMP, LIDAR_PHASE_TEMP)
304   CALL wxios_add_vaxis("cth16", MISR_N_CTH, MISR_CTH)
305#endif
306   
307    zdtimemoy_cosp = freq_COSP         ! Frequence ou l on moyenne
308
309    DO iff=1,3
310       zoutm_cosp(iff) = cosp_ecritfiles(iff) ! Frequence ou l on ecrit en seconde
311
312       IF (cosp_outfilekeys(iff)) THEN
313           CALL histbeg_phy_all(cosp_outfilenames(iff),itau_phy,zjulian,&
314             dtime,nhoricosp(iff),cosp_nidfiles(iff))
315!           print*,'histbeg_phy nhoricosp(iff),cosp_nidfiles(iff)', &
316!                    nhoricosp(iff),cosp_nidfiles(iff)
317
318#ifdef CPP_XIOS
319        IF (.not. ok_all_xml) then
320         WRITE(lunout,*) 'wxios_add_file ',cosp_outfilenames(iff)
321         CALL wxios_add_file(cosp_outfilenames(iff),chfreq(iff),10)
322        ENDIF
323#endif
324
325#ifndef CPP_IOIPSL_NO_OUTPUT
326! Definition de l'axe vertical
327       if (use_vgrid) then
328! Axe vertical Cosp 40 niveaux (en m)
329      CALL histvert(cosp_nidfiles(iff),"height","height","m",vgrid%Nlvgrid,vgrid%z,nvert(iff))
330       else
331! Axe vertical modele LMDZ presnivs
332      CALL histvert(cosp_nidfiles(iff),"presnivs","Vertical levels","Pa",vgrid%Nlvgrid,presnivs,nvert(iff),"down")
333       endif
334! Axe vertical niveaux modele (en m)
335      CALL histvert(cosp_nidfiles(iff),"height_mlev","height_mlev","m",Nlevlmdz,vgrid%mz,nvertmcosp(iff))
336
337      CALL histvert(cosp_nidfiles(iff),"sza","solar_zenith_angle","degrees",PARASOL_NREFL,PARASOL_SZA,nvertp(iff))
338
339      CALL histvert(cosp_nidfiles(iff),"pressure2","pressure","mb",7,ISCCP_PC,nvertisccp(iff),"down")
340
341      CALL histvert(cosp_nidfiles(iff),"column","column","count",Ncolumns,column_ax(1:Ncolumns),nvertcol(iff))
342
343      CALL histvert(cosp_nidfiles(iff),"temp","temperature","C",LIDAR_NTEMP,LIDAR_PHASE_TEMP,nverttemp(iff))                                       
344      CALL histvert(cosp_nidfiles(iff),"cth16","altitude","m",MISR_N_CTH,MISR_CTH,nvertmisr(iff))                                                                                                 
345!!! Valeur indefinie en cas IOIPSL
346     Cosp_fill_value=0.
347
348#endif
349
350      ENDIF
351  ENDDO
352
353    end SUBROUTINE cosp_output_open
354
355 END MODULE cosp_output_mod
Note: See TracBrowser for help on using the repository browser.