source: LMDZ5/branches/testing/libf/phylmd/cosp/cosp_output_mod.F90 @ 2594

Last change on this file since 2594 was 2594, checked in by Laurent Fairhead, 8 years ago

Merged trunk changes r2545:2589 into testing branch

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