1 | ! %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
2 | ! Copyright (c) 2015, Regents of the University of Colorado |
---|
3 | ! All rights reserved. |
---|
4 | ! |
---|
5 | ! Redistribution and use in source and binary forms, with or without modification, are |
---|
6 | ! permitted provided that the following conditions are met: |
---|
7 | ! |
---|
8 | ! 1. Redistributions of source code must retain the above copyright notice, this list of |
---|
9 | ! conditions and the following disclaimer. |
---|
10 | ! |
---|
11 | ! 2. Redistributions in binary form must reproduce the above copyright notice, this list |
---|
12 | ! of conditions and the following disclaimer in the documentation and/or other |
---|
13 | ! materials provided with the distribution. |
---|
14 | ! |
---|
15 | ! 3. Neither the name of the copyright holder nor the names of its contributors may be |
---|
16 | ! used to endorse or promote products derived from this software without specific prior |
---|
17 | ! written permission. |
---|
18 | ! |
---|
19 | ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY |
---|
20 | ! EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF |
---|
21 | ! MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL |
---|
22 | ! THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, |
---|
23 | ! SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT |
---|
24 | ! OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS |
---|
25 | ! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT |
---|
26 | ! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE |
---|
27 | ! OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. |
---|
28 | ! |
---|
29 | ! History: |
---|
30 | ! Jul 2007 - A. Bodas-Salcedo - Initial version |
---|
31 | ! Jul 2008 - A. Bodas-Salcedo - Added definitions of ISCCP axes |
---|
32 | ! Oct 2008 - H. Chepfer - Added PARASOL_NREFL |
---|
33 | ! Jun 2010 - R. Marchand - Modified to support quickbeam V3, added ifdef for |
---|
34 | ! hydrometeor definitions |
---|
35 | ! May 2015 - D. Swales - Tidied up. Set up appropriate fields during initialization. |
---|
36 | ! June 2015- D. Swales - Moved hydrometeor class variables to hydro_class_init in |
---|
37 | ! the module quickbeam_optics. |
---|
38 | ! Mar 2016 - D. Swales - Added scops_ccfrac. Was previously hardcoded in prec_scops.f90. |
---|
39 | ! Mar 2018 - R. Guzman - Added LIDAR_NTYPE for the OPAQ diagnostics |
---|
40 | ! Apr 2018 - R. Guzman - Added parameters for GROUND LIDAR and ATLID simulators |
---|
41 | ! |
---|
42 | ! %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
---|
43 | |
---|
44 | MODULE MOD_COSP_CONFIG |
---|
45 | USE COSP_KINDS, ONLY: wp,dp |
---|
46 | IMPLICIT NONE |
---|
47 | |
---|
48 | ! ##################################################################################### |
---|
49 | ! Common COSP information |
---|
50 | ! ##################################################################################### |
---|
51 | character(len=32) :: & |
---|
52 | COSP_VERSION ! COSP Version ID (set in cosp_interface_init) |
---|
53 | real(wp),parameter :: & |
---|
54 | R_UNDEF = -1.0E30, & ! Missing value |
---|
55 | R_GROUND = -1.0E20, & ! Flag for below ground results |
---|
56 | scops_ccfrac = 0.05 ! Fraction of column (or subcolumn) covered with convective |
---|
57 | ! precipitation (default is 5%). *NOTE* This quantity may vary |
---|
58 | ! between modeling centers. |
---|
59 | logical :: & |
---|
60 | use_vgrid ! True=Use new grid for L3 CLOUDAT and CALIPSO |
---|
61 | integer,parameter :: & |
---|
62 | SR_BINS = 15, & ! Number of bins (backscattering coefficient) in CALOPSO LIDAR simulator. |
---|
63 | N_HYDRO = 9 ! Number of hydrometeor classes used by quickbeam radar simulator. |
---|
64 | |
---|
65 | ! Mode debug ou prod (AI 0302018) |
---|
66 | logical :: ok_debug_cosp = .true. |
---|
67 | ! #################################################################################### |
---|
68 | ! Joint histogram bin-boundaries |
---|
69 | ! tau is used by ISCCP and MISR |
---|
70 | ! pres is used by ISCCP |
---|
71 | ! hgt is used by MISR |
---|
72 | ! ReffLiq is used by MODIS |
---|
73 | ! ReffIce is used by MODIS |
---|
74 | ! *NOTE* ALL JOINT-HISTOGRAM BIN BOUNDARIES ARE DECLARED AND DEFINED HERE IN |
---|
75 | ! COSP_CONFIG, WITH THE EXCEPTION OF THE TAU AXIS USED BY THE MODIS SIMULATOR, |
---|
76 | ! WHICH IS SET DURING INITIALIZATION IN COSP_INTERFACE_INIT. |
---|
77 | ! #################################################################################### |
---|
78 | ! Optical depth bin axis |
---|
79 | integer,parameter :: & |
---|
80 | ntau=7 |
---|
81 | real(wp),parameter,dimension(ntau+1) :: & |
---|
82 | tau_binBounds = (/0.0, 0.3, 1.3, 3.6, 9.4, 23., 60., 10000./) |
---|
83 | real(wp),parameter,dimension(ntau) :: & |
---|
84 | tau_binCenters = (/0.15, 0.80, 2.45, 6.5, 16.2, 41.5, 100.0/) |
---|
85 | real(wp),parameter,dimension(2,ntau) :: & |
---|
86 | tau_binEdges = reshape(source=(/0.0, 0.3, 0.3, 1.3, 1.3, 3.6, 3.6, & |
---|
87 | 9.4, 9.4, 23.0, 23.0, 60.0, 60.0, 100000.0/), & |
---|
88 | shape=(/2,ntau/)) |
---|
89 | |
---|
90 | ! Optical depth bin axes (ONLY USED BY MODIS SIMULATOR IN v1.4) |
---|
91 | integer :: l,k |
---|
92 | integer,parameter :: & |
---|
93 | ntauV1p4 = 6 |
---|
94 | real(wp),parameter,dimension(ntauV1p4+1) :: & |
---|
95 | tau_binBoundsV1p4 = (/0.3, 1.3, 3.6, 9.4, 23., 60., 10000./) |
---|
96 | real(wp),parameter,dimension(2,ntauV1p4) :: & |
---|
97 | tau_binEdgesV1p4 = reshape(source =(/tau_binBoundsV1p4(1),((tau_binBoundsV1p4(k),l=1,2), & |
---|
98 | k=2,ntauV1p4),100000._wp/),shape = (/2,ntauV1p4/)) |
---|
99 | real(wp),parameter,dimension(ntauV1p4) :: & |
---|
100 | tau_binCentersV1p4 = (tau_binEdgesV1p4(1,:)+tau_binEdgesV1p4(2,:))/2._wp |
---|
101 | |
---|
102 | ! Cloud-top height pressure bin axis |
---|
103 | integer,parameter :: & |
---|
104 | npres = 7 |
---|
105 | real(wp),parameter,dimension(npres+1) :: & |
---|
106 | pres_binBounds = (/0., 180., 310., 440., 560., 680., 800., 10000./) |
---|
107 | real(wp),parameter,dimension(npres) :: & |
---|
108 | pres_binCenters = (/90000., 74000., 62000., 50000., 37500., 24500., 9000./) |
---|
109 | real(wp),parameter,dimension(2,npres) :: & |
---|
110 | pres_binEdges = reshape(source=(/100000.0, 80000.0, 80000.0, 68000.0, 68000.0, & |
---|
111 | 56000.0, 56000.0, 44000.0, 44000.0, 31000.0, & |
---|
112 | 31000.0, 18000.0, 18000.0, 0.0/), & |
---|
113 | shape=(/2,npres/)) |
---|
114 | |
---|
115 | ! Cloud-top height bin axis #1 |
---|
116 | integer,parameter :: & |
---|
117 | nhgt = 16 |
---|
118 | real(wp),parameter,dimension(nhgt+1) :: & |
---|
119 | hgt_binBounds = (/-.99,0.,0.5,1.,1.5,2.,2.5,3.,4.,5.,7.,9.,11.,13.,15.,17.,99./) |
---|
120 | real(wp),parameter,dimension(nhgt) :: & |
---|
121 | hgt_binCenters = 1000*(/0.,0.25,0.75,1.25,1.75,2.25,2.75,3.5,4.5,6.,8.,10.,12., & |
---|
122 | 14.5,16.,18./) |
---|
123 | real(wp),parameter,dimension(2,nhgt) :: & |
---|
124 | hgt_binEdges = 1000.0*reshape(source=(/-99.0, 0.0, 0.0, 0.5, 0.5, 1.0, 1.0, 1.5, & |
---|
125 | 1.5, 2.0, 2.0, 2.5, 2.5, 3.0, 3.0, 4.0, & |
---|
126 | 4.0, 5.0, 5.0, 7.0, 7.0, 9.0, 9.0,11.0, & |
---|
127 | 11.0,13.0,13.0,15.0,15.0,17.0,17.0,99.0/),& |
---|
128 | shape=(/2,nhgt/)) |
---|
129 | |
---|
130 | ! Liquid and Ice particle bins for MODIS joint histogram of optical-depth and particle |
---|
131 | ! size |
---|
132 | integer :: i,j |
---|
133 | integer,parameter :: & |
---|
134 | nReffLiq = 6, & ! Number of bins for tau/ReffLiq joint-histogram |
---|
135 | nReffIce = 6 ! Number of bins for tau/ReffICE joint-histogram |
---|
136 | real(wp),parameter,dimension(nReffLiq+1) :: & |
---|
137 | reffLIQ_binBounds = (/0., 8e-6, 1.0e-5, 1.3e-5, 1.5e-5, 2.0e-5, 3.0e-5/) |
---|
138 | real(wp),parameter,dimension(nReffIce+1) :: & |
---|
139 | reffICE_binBounds = (/0., 1.0e-5, 2.0e-5, 3.0e-5, 4.0e-5, 6.0e-5, 9.0e-5/) |
---|
140 | real(wp),parameter,dimension(2,nReffICE) :: & |
---|
141 | reffICE_binEdges = reshape(source=(/reffICE_binBounds(1),((reffICE_binBounds(k), & |
---|
142 | l=1,2),k=2,nReffICE),reffICE_binBounds(nReffICE+1)/), & |
---|
143 | shape = (/2,nReffICE/)) |
---|
144 | real(wp),parameter,dimension(2,nReffLIQ) :: & |
---|
145 | reffLIQ_binEdges = reshape(source=(/reffLIQ_binBounds(1),((reffLIQ_binBounds(k), & |
---|
146 | l=1,2),k=2,nReffLIQ),reffLIQ_binBounds(nReffICE+1)/), & |
---|
147 | shape = (/2,nReffLIQ/)) |
---|
148 | real(wp),parameter,dimension(nReffICE) :: & |
---|
149 | reffICE_binCenters = (reffICE_binEdges(1,:)+reffICE_binEdges(2,:))/2._wp |
---|
150 | real(wp),parameter,dimension(nReffLIQ) :: & |
---|
151 | reffLIQ_binCenters = (reffLIQ_binEdges(1,:)+reffLIQ_binEdges(2,:))/2._wp |
---|
152 | |
---|
153 | ! #################################################################################### |
---|
154 | ! Constants used by RTTOV. |
---|
155 | ! #################################################################################### |
---|
156 | integer,parameter :: & |
---|
157 | RTTOV_MAX_CHANNELS = 20 |
---|
158 | character(len=256),parameter :: & |
---|
159 | rttovDir = '/homedata/rguzman/CALIPSO/RTTOV/rttov_11.3/' |
---|
160 | ! #################################################################################### |
---|
161 | ! Constants used by the PARASOL simulator. |
---|
162 | ! #################################################################################### |
---|
163 | integer,parameter :: & |
---|
164 | PARASOL_NREFL = 5, & ! Number of angles in LUT |
---|
165 | PARASOL_NTAU = 7 ! Number of optical depths in LUT |
---|
166 | real(wp),parameter,dimension(PARASOL_NREFL) :: & |
---|
167 | PARASOL_SZA = (/0.0, 20.0, 40.0, 60.0, 80.0/) |
---|
168 | REAL(WP),parameter,dimension(PARASOL_NTAU) :: & |
---|
169 | PARASOL_TAU = (/0., 1., 5., 10., 20., 50., 100./) |
---|
170 | |
---|
171 | ! LUTs |
---|
172 | REAL(WP),parameter,dimension(PARASOL_NREFL,PARASOL_NTAU) :: & |
---|
173 | ! LUT for liquid particles |
---|
174 | rlumA = reshape(source=(/ 0.03, 0.03, 0.03, 0.03, 0.03, & |
---|
175 | 0.090886, 0.072185, 0.058410, 0.052498, 0.034730, & |
---|
176 | 0.283965, 0.252596, 0.224707, 0.175844, 0.064488, & |
---|
177 | 0.480587, 0.436401, 0.367451, 0.252916, 0.081667, & |
---|
178 | 0.695235, 0.631352, 0.509180, 0.326551, 0.098215, & |
---|
179 | 0.908229, 0.823924, 0.648152, 0.398581, 0.114411, & |
---|
180 | 1.0, 0.909013, 0.709554, 0.430405, 0.121567/), & |
---|
181 | shape=(/PARASOL_NREFL,PARASOL_NTAU/)), & |
---|
182 | ! LUT for ice particles |
---|
183 | rlumB = reshape(source=(/ 0.03, 0.03, 0.03, 0.03, 0.03, & |
---|
184 | 0.092170, 0.087082, 0.083325, 0.084935, 0.054157, & |
---|
185 | 0.311941, 0.304293, 0.285193, 0.233450, 0.089911, & |
---|
186 | 0.511298, 0.490879, 0.430266, 0.312280, 0.107854, & |
---|
187 | 0.712079, 0.673565, 0.563747, 0.382376, 0.124127, & |
---|
188 | 0.898243, 0.842026, 0.685773, 0.446371, 0.139004, & |
---|
189 | 0.976646, 0.912966, 0.737154, 0.473317, 0.145269/), & |
---|
190 | shape=(/PARASOL_NREFL,PARASOL_NTAU/)) |
---|
191 | |
---|
192 | ! #################################################################################### |
---|
193 | ! ISCCP simulator tau/CTP joint histogram information |
---|
194 | ! #################################################################################### |
---|
195 | integer,parameter :: & |
---|
196 | numISCCPTauBins = ntau, & ! Number of optical depth bins |
---|
197 | numISCCPPresBins = npres ! Number of pressure bins |
---|
198 | real(wp),parameter,dimension(ntau+1) :: & |
---|
199 | isccp_histTau = tau_binBounds ! Joint-histogram boundaries (optical depth) |
---|
200 | real(wp),parameter,dimension(npres+1) :: & |
---|
201 | isccp_histPres = pres_binBounds ! Joint-histogram boundaries (cloud pressure) |
---|
202 | real(wp),parameter,dimension(ntau) :: & |
---|
203 | isccp_histTauCenters = tau_binCenters ! Joint histogram bin centers (optical depth) |
---|
204 | real(wp),parameter,dimension(npres) :: & |
---|
205 | isccp_histPresCenters = pres_binCenters ! Joint histogram bin centers (cloud pressure) |
---|
206 | real(wp),parameter,dimension(2,ntau) :: & |
---|
207 | isccp_histTauEdges = tau_binEdges ! Joint histogram bin edges (optical depth) |
---|
208 | real(wp),parameter,dimension(2,npres) :: & |
---|
209 | isccp_histPresEdges = pres_binEdges ! Joint histogram bin edges (cloud pressure) |
---|
210 | |
---|
211 | ! #################################################################################### |
---|
212 | ! MISR simulator tau/CTH joint histogram information |
---|
213 | ! #################################################################################### |
---|
214 | integer,parameter :: & |
---|
215 | numMISRHgtBins = nhgt, & ! Number of cloud-top height bins |
---|
216 | numMISRTauBins = ntau ! Number of optical depth bins |
---|
217 | ! Joint histogram boundaries |
---|
218 | real(wp),parameter,dimension(numMISRHgtBins+1) :: & |
---|
219 | misr_histHgt = hgt_binBounds ! Joint-histogram boundaries (cloud height) |
---|
220 | real(wp),parameter,dimension(numMISRTauBins+1) :: & |
---|
221 | misr_histTau = tau_binBounds ! Joint-histogram boundaries (optical-depth) |
---|
222 | real(wp),parameter,dimension(numMISRHgtBins) :: & |
---|
223 | misr_histHgtCenters = hgt_binCenters ! Joint-histogram bin centers (cloud height) |
---|
224 | real(wp),parameter,dimension(2,numMISRHgtBins) :: & |
---|
225 | misr_histHgtEdges = hgt_BinEdges ! Joint-histogram bin edges (cloud height) |
---|
226 | |
---|
227 | ! #################################################################################### |
---|
228 | ! MODIS simulator tau/CTP joint histogram information |
---|
229 | ! #################################################################################### |
---|
230 | integer,parameter :: & |
---|
231 | numMODISPresBins = npres ! Number of pressure bins for joint-histogram |
---|
232 | real(wp),parameter,dimension(numMODISPresBins + 1) :: & |
---|
233 | modis_histPres = 100*pres_binBounds ! Joint-histogram boundaries (cloud pressure) |
---|
234 | real(wp),parameter,dimension(2, numMODISPresBins) :: & |
---|
235 | modis_histPresEdges = 100*pres_binEdges ! Joint-histogram bin edges (cloud pressure) |
---|
236 | real(wp),parameter,dimension(numMODISPresBins) :: & |
---|
237 | modis_histPresCenters = 100*pres_binCenters ! Joint-histogram bin centers (cloud pressure) |
---|
238 | |
---|
239 | ! For the MODIS simulator we want to preserve the ability for cospV1.4.0 to use the |
---|
240 | ! old histogram bin boundaries for optical depth, so these are set up in initialization. |
---|
241 | integer :: & |
---|
242 | numMODISTauBins ! Number of tau bins for joint-histogram |
---|
243 | real(wp),save,allocatable,dimension(:) :: & |
---|
244 | modis_histTau ! Joint-histogram boundaries (optical depth) |
---|
245 | !$OMP THREADPRIVATE(modis_histTau) |
---|
246 | real(wp),save,allocatable,dimension(:,:) :: & |
---|
247 | modis_histTauEdges ! Joint-histogram bin edges (optical depth) |
---|
248 | !$OMP THREADPRIVATE(modis_histTauEdges) |
---|
249 | real(wp),save,allocatable,dimension(:) :: & |
---|
250 | modis_histTauCenters ! Joint-histogram bin centers (optical depth) |
---|
251 | !$OMP THREADPRIVATE(modis_histTauCenters) |
---|
252 | |
---|
253 | ! #################################################################################### |
---|
254 | ! MODIS simulator tau/ReffICE and tau/ReffLIQ joint-histogram information |
---|
255 | ! #################################################################################### |
---|
256 | ! Ice |
---|
257 | integer,parameter :: & |
---|
258 | numMODISReffIceBins = nReffIce ! Number of bins for joint-histogram |
---|
259 | real(wp),parameter,dimension(nReffIce+1) :: & |
---|
260 | modis_histReffIce = reffICE_binBounds ! Effective radius bin boundaries |
---|
261 | real(wp),parameter,dimension(nReffIce) :: & |
---|
262 | modis_histReffIceCenters = reffICE_binCenters ! Effective radius bin centers |
---|
263 | real(wp),parameter,dimension(2,nReffICE) :: & |
---|
264 | modis_histReffIceEdges = reffICE_binEdges ! Effective radius bin edges |
---|
265 | |
---|
266 | ! Liquid |
---|
267 | integer,parameter :: & |
---|
268 | numMODISReffLiqBins = nReffLiq ! Number of bins for joint-histogram |
---|
269 | real(wp),parameter,dimension(nReffLiq+1) :: & |
---|
270 | modis_histReffLiq = reffLIQ_binBounds ! Effective radius bin boundaries |
---|
271 | real(wp),parameter,dimension(nReffLiq) :: & |
---|
272 | modis_histReffLiqCenters = reffICE_binCenters ! Effective radius bin centers |
---|
273 | real(wp),parameter,dimension(2,nReffICE) :: & |
---|
274 | modis_histReffLiqEdges = reffLIQ_binEdges ! Effective radius bin edges |
---|
275 | |
---|
276 | ! #################################################################################### |
---|
277 | ! CLOUDSAT reflectivity histogram information |
---|
278 | ! #################################################################################### |
---|
279 | integer,parameter :: & |
---|
280 | CLOUDSAT_DBZE_BINS = 15, & ! Number of dBZe bins in histogram (cfad) |
---|
281 | CLOUDSAT_DBZE_MIN = -100, & ! Minimum value for radar reflectivity |
---|
282 | CLOUDSAT_DBZE_MAX = 80, & ! Maximum value for radar reflectivity |
---|
283 | CLOUDSAT_CFAD_ZE_MIN = -50, & ! Lower value of the first CFAD Ze bin |
---|
284 | CLOUDSAT_CFAD_ZE_WIDTH = 5 ! Bin width (dBZe) |
---|
285 | |
---|
286 | real(wp),parameter,dimension(CLOUDSAT_DBZE_BINS+1) :: & |
---|
287 | cloudsat_histRef = (/CLOUDSAT_DBZE_MIN,(/(i, i=int(CLOUDSAT_CFAD_ZE_MIN+CLOUDSAT_CFAD_ZE_WIDTH),& |
---|
288 | int(CLOUDSAT_CFAD_ZE_MIN+(CLOUDSAT_DBZE_BINS-1)*CLOUDSAT_CFAD_ZE_WIDTH), & |
---|
289 | int(CLOUDSAT_CFAD_ZE_WIDTH))/),CLOUDSAT_DBZE_MAX/) |
---|
290 | real(wp),parameter,dimension(2,CLOUDSAT_DBZE_BINS) :: & |
---|
291 | cloudsat_binEdges = reshape(source=(/cloudsat_histRef(1),((cloudsat_histRef(k), & |
---|
292 | l=1,2),k=2,CLOUDSAT_DBZE_BINS),cloudsat_histRef(CLOUDSAT_DBZE_BINS+1)/),& |
---|
293 | shape = (/2,CLOUDSAT_DBZE_BINS/)) |
---|
294 | real(wp),parameter,dimension(CLOUDSAT_DBZE_BINS) :: & |
---|
295 | cloudsat_binCenters = (cloudsat_binEdges(1,:)+cloudsat_binEdges(2,:))/2._wp |
---|
296 | |
---|
297 | ! Parameters for Cloudsat near-surface precipitation diagnostics. |
---|
298 | ! Precipitation classes. |
---|
299 | integer, parameter :: & |
---|
300 | nCloudsatPrecipClass = 10 |
---|
301 | integer, parameter :: & |
---|
302 | pClass_noPrecip = 0, & ! No precipitation |
---|
303 | pClass_Rain1 = 1, & ! Rain possible |
---|
304 | pClass_Rain2 = 2, & ! Rain probable |
---|
305 | pClass_Rain3 = 3, & ! Rain certain |
---|
306 | pClass_Snow1 = 4, & ! Snow possible |
---|
307 | pClass_Snow2 = 5, & ! Snow certain |
---|
308 | pClass_Mixed1 = 6, & ! Mixed-precipitation possible |
---|
309 | pClass_Mixed2 = 7, & ! Mixed-precipitation certain |
---|
310 | pClass_Rain4 = 8, & ! Heavy rain |
---|
311 | pClass_default = 9 ! Default |
---|
312 | ! Reflectivity bin boundaries, used by decision tree to classify precipitation type. |
---|
313 | real(wp), dimension(4),parameter :: & |
---|
314 | Zenonbinval =(/0._wp, -5._wp, -7.5_wp, -15._wp/) |
---|
315 | real(wp), dimension(6),parameter :: & |
---|
316 | Zbinvallnd = (/10._wp, 5._wp, 2.5_wp, -2.5_wp, -5._wp, -15._wp/) |
---|
317 | ! Vertical level index(Nlvgrid) for Cloudsat precipitation occurence/frequency diagnostics. |
---|
318 | ! Level 39 of Nlvgrid(40) is 480-960m. |
---|
319 | ! integer, parameter :: & !PREC_BUG |
---|
320 | ! cloudsat_preclvl = 39 !PREC_BUG |
---|
321 | |
---|
322 | ! #################################################################################### |
---|
323 | ! Parameters used by the CALIPSO LIDAR simulator |
---|
324 | ! #################################################################################### |
---|
325 | ! CALISPO backscatter histogram bins |
---|
326 | real(wp),parameter :: & |
---|
327 | S_cld = 5.0, & ! Threshold for cloud detection |
---|
328 | S_att = 0.01, & ! |
---|
329 | S_cld_att = 30. ! Threshold for undefined cloud phase detection |
---|
330 | real(wp),parameter,dimension(SR_BINS+1) :: & |
---|
331 | calipso_histBsct = (/-1.,0.01,1.2,3.0,5.0,7.0,10.0,15.0,20.0,25.0,30.0,40.0,50.0, & |
---|
332 | 60.0,80.0,999./) ! Backscatter histogram bins |
---|
333 | real(wp),parameter,dimension(2,SR_BINS) :: & |
---|
334 | calipso_binEdges = reshape(source=(/calipso_histBsct(1),((calipso_histBsct(k), & |
---|
335 | l=1,2),k=2,SR_BINS),calipso_histBsct(SR_BINS+1)/), & |
---|
336 | shape = (/2,SR_BINS/)) |
---|
337 | real(wp),parameter,dimension(SR_BINS) :: & |
---|
338 | calipso_binCenters = (calipso_binEdges(1,:)+calipso_binEdges(2,:))/2._wp |
---|
339 | |
---|
340 | integer,parameter :: & |
---|
341 | LIDAR_NTEMP = 40, & |
---|
342 | LIDAR_NCAT = 4, & ! Number of categories for cloudtop heights (high/mid/low/tot) |
---|
343 | LIDAR_NTYPE = 3 ! Number of categories for OPAQ (opaque/thin cloud + z_opaque) |
---|
344 | real(wp),parameter,dimension(LIDAR_NTEMP) :: & |
---|
345 | LIDAR_PHASE_TEMP= & |
---|
346 | (/-91.5,-88.5,-85.5,-82.5,-79.5,-76.5,-73.5,-70.5,-67.5,-64.5, & |
---|
347 | -61.5,-58.5,-55.5,-52.5,-49.5,-46.5,-43.5,-40.5,-37.5,-34.5, & |
---|
348 | -31.5,-28.5,-25.5,-22.5,-19.5,-16.5,-13.5,-10.5, -7.5, -4.5, & |
---|
349 | -1.5, 1.5, 4.5, 7.5, 10.5, 13.5, 16.5, 19.5, 22.5, 25.5/) |
---|
350 | real(wp),parameter,dimension(2,LIDAR_NTEMP) :: & |
---|
351 | LIDAR_PHASE_TEMP_BNDS=reshape(source= & |
---|
352 | (/-273.15, -90., -90., -87., -87., -84., -84., -81., -81., -78., & |
---|
353 | -78., -75., -75., -72., -72., -69., -69., -66., -66., -63., & |
---|
354 | -63., -60., -60., -57., -57., -54., -54., -51., -51., -48., & |
---|
355 | -48., -45., -45., -42., -42., -39., -39., -36., -36., -33., & |
---|
356 | -33., -30., -30., -27., -27., -24., -24., -21., -21., -18., & |
---|
357 | -18., -15., -15., -12., -12., -9., -9., -6., -6., -3., & |
---|
358 | -3., 0., 0., 3., 3., 6., 6., 9., 9., 12., & |
---|
359 | 12., 15., 15., 18., 18., 21., 21., 24., 24., 100. /), & |
---|
360 | shape=(/2,40/)) |
---|
361 | |
---|
362 | ! #################################################################################### |
---|
363 | ! Parameters used by the GROUND LIDAR simulator |
---|
364 | ! #################################################################################### |
---|
365 | ! GROUND LIDAR backscatter histogram bins |
---|
366 | ! real(wp),parameter :: & |
---|
367 | ! S_cld = 5.0, & ! Threshold for cloud detection |
---|
368 | ! S_att = 0.01, & ! |
---|
369 | ! S_cld_att = 30. ! Threshold for undefined cloud phase detection |
---|
370 | real(wp),parameter,dimension(SR_BINS+1) :: & |
---|
371 | grLidar532_histBsct = (/-1.,0.01,1.2,3.0,5.0,7.0,10.0,15.0,20.0,25.0,30.0,40.0,50.0, & |
---|
372 | 60.0,80.0,999./) ! Backscatter histogram bins |
---|
373 | real(wp),parameter,dimension(2,SR_BINS) :: & |
---|
374 | grLidar532_binEdges = reshape(source=(/grLidar532_histBsct(1),((grLidar532_histBsct(k), & |
---|
375 | l=1,2),k=2,SR_BINS),grLidar532_histBsct(SR_BINS+1)/), & |
---|
376 | shape = (/2,SR_BINS/)) |
---|
377 | real(wp),parameter,dimension(SR_BINS) :: & |
---|
378 | grLidar532_binCenters = (grLidar532_binEdges(1,:)+grLidar532_binEdges(2,:))/2._wp |
---|
379 | |
---|
380 | ! integer,parameter :: & |
---|
381 | ! LIDAR_NCAT = 4 ! Number of categories for cloudtop heights (high/mid/low/tot) |
---|
382 | |
---|
383 | ! #################################################################################### |
---|
384 | ! Parameters used by the ATLID LIDAR simulator |
---|
385 | ! #################################################################################### |
---|
386 | ! ATLID LIDAR backscatter histogram bins |
---|
387 | real(wp),parameter :: & |
---|
388 | S_cld_atlid = 1.74, & ! Threshold for cloud detection |
---|
389 | S_att_atlid = 0.01, & ! |
---|
390 | S_cld_att_atlid = 6.67 ! Threshold for undefined cloud phase detection |
---|
391 | real(wp),parameter,dimension(SR_BINS+1) :: & |
---|
392 | atlid_histBsct = (/-1.,0.01,1.03,1.38,1.74,2.07,2.62,3.65,4.63,5.63,6.67,8.8,11.25, & |
---|
393 | 13.2,17.2,999./) ! Backscatter histogram bins |
---|
394 | real(wp),parameter,dimension(2,SR_BINS) :: & |
---|
395 | atlid_binEdges = reshape(source=(/atlid_histBsct(1),((atlid_histBsct(k), & |
---|
396 | l=1,2),k=2,SR_BINS),atlid_histBsct(SR_BINS+1)/), & |
---|
397 | shape = (/2,SR_BINS/)) |
---|
398 | real(wp),parameter,dimension(SR_BINS) :: & |
---|
399 | atlid_binCenters = (atlid_binEdges(1,:)+atlid_binEdges(2,:))/2._wp |
---|
400 | |
---|
401 | ! integer,parameter :: & |
---|
402 | ! LIDAR_NCAT = 4 ! Number of categories for cloudtop heights (high/mid/low/tot) |
---|
403 | |
---|
404 | ! #################################################################################### |
---|
405 | ! New vertical grid used by CALIPSO and CLOUDSAT L3 (set up during initialization) |
---|
406 | ! #################################################################################### |
---|
407 | integer :: & |
---|
408 | Nlvgrid ! Number of levels in New grid |
---|
409 | real(wp),dimension(:), save, allocatable :: & |
---|
410 | vgrid_zl, & ! New grid bottoms |
---|
411 | vgrid_zu, & ! New grid tops |
---|
412 | vgrid_z ! New grid center |
---|
413 | !$OMP THREADPRIVATE(vgrid_zl,vgrid_zu,vgrid_z) |
---|
414 | |
---|
415 | ! #################################################################################### |
---|
416 | ! Vertical grid used by CALIPSO and CLOUDSAT L3 (LMDZ parameter) |
---|
417 | ! #################################################################################### |
---|
418 | |
---|
419 | integer, parameter :: & |
---|
420 | niv_sorties = 40 |
---|
421 | real(wp),parameter,dimension(niv_sorties) :: & |
---|
422 | vgrid_z_in = (/240.0, 720.0, 1200.0, 1680.0, 2160.0, 2640.0, 3120.0, 3600.0, & |
---|
423 | 4080.0, 4560.0, 5040.0, 5520.0, 6000.0, 6480.0, 6960.0, 7440.0, & |
---|
424 | 7920.0, 8400.0, 8880.0, 9360.0, 9840.0, 10320.0, 10800.0, & |
---|
425 | 11280.0, 11760.0, 12240.0, 12720.0, 13200.0, 13680.0, 14160.0, & |
---|
426 | 14640.0, 15120.0, 15600.0, 16080.0, 16560.0, 17040.0, 17520.0, & |
---|
427 | 18000.0, 18480.0, 18960.0/) |
---|
428 | |
---|
429 | END MODULE MOD_COSP_CONFIG |
---|