source: LMDZ5/trunk/libf/phylmd/cosp/cosp_output_mod.F90 @ 2740

Last change on this file since 2740 was 2713, checked in by idelkadi, 8 years ago

Mise a jour du simulateur COSP.
Passage de la version 1.4.0 a la version 1.4.1
(Version suggeree pour CFMIP3/CMIP6)

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