source: LMDZ6/branches/Ocean_skin/libf/phylmd/cosp2/cosp_output_mod.F90 @ 3605

Last change on this file since 3605 was 3605, checked in by lguez, 4 years ago

Merge revisions 3427:3600 of trunk into branch Ocean_skin

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