source: LMDZ6/trunk/libf/phylmdiso/cospv2/cosp_config.F90 @ 3927

Last change on this file since 3927 was 3927, checked in by Laurent Fairhead, 3 years ago

Initial import of the physics wih isotopes from Camille Risi
CR

File size: 25.4 KB
Line 
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
44MODULE 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    ! #################################################################################### 
66    ! Joint histogram bin-boundaries
67    ! tau is used by ISCCP and MISR
68    ! pres is used by ISCCP
69    ! hgt is used by MISR
70    ! ReffLiq is used by MODIS
71    ! ReffIce is used by MODIS
72    ! *NOTE* ALL JOINT-HISTOGRAM BIN BOUNDARIES ARE DECLARED AND DEFINED HERE IN
73    !        COSP_CONFIG, WITH THE EXCEPTION OF THE TAU AXIS USED BY THE MODIS SIMULATOR,
74    !        WHICH IS SET DURING INITIALIZATION IN COSP_INTERFACE_INIT.
75    ! ####################################################################################
76    ! Optical depth bin axis
77    integer,parameter :: &
78         ntau=7 
79    real(wp),parameter,dimension(ntau+1) :: &
80       tau_binBounds = (/0.0, 0.3, 1.3, 3.6, 9.4, 23., 60., 10000./)
81    real(wp),parameter,dimension(ntau) :: &
82         tau_binCenters = (/0.15, 0.80, 2.45, 6.5, 16.2, 41.5, 100.0/)
83    real(wp),parameter,dimension(2,ntau) :: &
84         tau_binEdges = reshape(source=(/0.0, 0.3,  0.3,  1.3,  1.3,  3.6,      3.6,     &
85                                         9.4, 9.4, 23.0, 23.0, 60.0, 60.0, 100000.0/),   &
86                                         shape=(/2,ntau/))
87
88    ! Optical depth bin axes (ONLY USED BY MODIS SIMULATOR IN v1.4)
89    integer :: l,k
90    integer,parameter :: &
91         ntauV1p4 = 6
92    real(wp),parameter,dimension(ntauV1p4+1) :: &
93         tau_binBoundsV1p4 = (/0.3, 1.3, 3.6, 9.4, 23., 60., 10000./)
94    real(wp),parameter,dimension(2,ntauV1p4) :: &
95         tau_binEdgesV1p4 = reshape(source =(/tau_binBoundsV1p4(1),((tau_binBoundsV1p4(k),l=1,2),   &
96                                             k=2,ntauV1p4),100000._wp/),shape = (/2,ntauV1p4/))
97    real(wp),parameter,dimension(ntauV1p4) :: &
98         tau_binCentersV1p4 = (tau_binEdgesV1p4(1,:)+tau_binEdgesV1p4(2,:))/2._wp 
99   
100    ! Cloud-top height pressure bin axis
101    integer,parameter :: &
102         npres = 7     
103    real(wp),parameter,dimension(npres+1) :: &
104         pres_binBounds = (/0., 180., 310., 440., 560., 680., 800., 10000./)
105    real(wp),parameter,dimension(npres) :: &
106         pres_binCenters = (/90000., 74000., 62000., 50000., 37500., 24500., 9000./)   
107    real(wp),parameter,dimension(2,npres) :: &
108         pres_binEdges = reshape(source=(/100000.0, 80000.0, 80000.0, 68000.0, 68000.0,    &
109                                           56000.0, 56000.0, 44000.0, 44000.0, 31000.0,    &
110                                           31000.0, 18000.0, 18000.0,     0.0/),           &
111                                           shape=(/2,npres/))
112
113    ! Cloud-top height bin axis #1
114    integer,parameter :: &
115         nhgt = 16
116    real(wp),parameter,dimension(nhgt+1) :: &
117         hgt_binBounds = (/-.99,0.,0.5,1.,1.5,2.,2.5,3.,4.,5.,7.,9.,11.,13.,15.,17.,99./)
118    real(wp),parameter,dimension(nhgt) :: &
119         hgt_binCenters = 1000*(/0.,0.25,0.75,1.25,1.75,2.25,2.75,3.5,4.5,6.,8.,10.,12.,   &
120         14.5,16.,18./) 
121    real(wp),parameter,dimension(2,nhgt) :: &
122         hgt_binEdges = 1000.0*reshape(source=(/-99.0, 0.0, 0.0, 0.5, 0.5, 1.0, 1.0, 1.5,  &
123                                                  1.5, 2.0, 2.0, 2.5, 2.5, 3.0, 3.0, 4.0,  &
124                                                  4.0, 5.0, 5.0, 7.0, 7.0, 9.0, 9.0,11.0,  &
125                                                  11.0,13.0,13.0,15.0,15.0,17.0,17.0,99.0/),&
126                                                  shape=(/2,nhgt/))   
127
128    ! Liquid and Ice particle bins for MODIS joint histogram of optical-depth and particle
129    ! size
130    integer :: i,j
131    integer,parameter :: &
132         nReffLiq = 6, & ! Number of bins for tau/ReffLiq joint-histogram
133         nReffIce = 6    ! Number of bins for tau/ReffICE joint-histogram
134    real(wp),parameter,dimension(nReffLiq+1) :: &
135         reffLIQ_binBounds = (/0., 8e-6, 1.0e-5, 1.3e-5, 1.5e-5, 2.0e-5, 3.0e-5/)
136    real(wp),parameter,dimension(nReffIce+1) :: &
137         reffICE_binBounds = (/0., 1.0e-5, 2.0e-5, 3.0e-5, 4.0e-5, 6.0e-5, 9.0e-5/)
138    real(wp),parameter,dimension(2,nReffICE) :: &
139         reffICE_binEdges = reshape(source=(/reffICE_binBounds(1),((reffICE_binBounds(k),  &
140                                    l=1,2),k=2,nReffICE),reffICE_binBounds(nReffICE+1)/),  &
141                                    shape = (/2,nReffICE/))
142    real(wp),parameter,dimension(2,nReffLIQ) :: &
143         reffLIQ_binEdges = reshape(source=(/reffLIQ_binBounds(1),((reffLIQ_binBounds(k),  &
144                                    l=1,2),k=2,nReffLIQ),reffLIQ_binBounds(nReffICE+1)/),  &
145                                    shape = (/2,nReffLIQ/))             
146    real(wp),parameter,dimension(nReffICE) :: &
147         reffICE_binCenters = (reffICE_binEdges(1,:)+reffICE_binEdges(2,:))/2._wp
148    real(wp),parameter,dimension(nReffLIQ) :: &
149         reffLIQ_binCenters = (reffLIQ_binEdges(1,:)+reffLIQ_binEdges(2,:))/2._wp
150
151    ! #################################################################################### 
152    ! Constants used by RTTOV.
153    ! #################################################################################### 
154    integer,parameter :: &
155         RTTOV_MAX_CHANNELS = 20
156    character(len=256),parameter :: &
157         rttovDir = '/homedata/rguzman/CALIPSO/RTTOV/rttov_11.3/'
158    ! #################################################################################### 
159    ! Constants used by the PARASOL simulator.
160    ! #################################################################################### 
161    integer,parameter :: &
162         PARASOL_NREFL = 5,  & ! Number of angles in LUT
163         PARASOL_NTAU  = 7     ! Number of optical depths in LUT
164    real(wp),parameter,dimension(PARASOL_NREFL) :: &
165         PARASOL_SZA = (/0.0, 20.0, 40.0, 60.0, 80.0/)
166    REAL(WP),parameter,dimension(PARASOL_NTAU) :: &
167         PARASOL_TAU = (/0., 1., 5., 10., 20., 50., 100./)
168   
169    ! LUTs
170    REAL(WP),parameter,dimension(PARASOL_NREFL,PARASOL_NTAU) :: &
171         ! LUT for liquid particles
172         rlumA = reshape(source=(/ 0.03,     0.03,     0.03,     0.03,     0.03,         &
173                                   0.090886, 0.072185, 0.058410, 0.052498, 0.034730,     &
174                                   0.283965, 0.252596, 0.224707, 0.175844, 0.064488,     &
175                                   0.480587, 0.436401, 0.367451, 0.252916, 0.081667,     &
176                                   0.695235, 0.631352, 0.509180, 0.326551, 0.098215,     &
177                                   0.908229, 0.823924, 0.648152, 0.398581, 0.114411,     &
178                                   1.0,      0.909013, 0.709554, 0.430405, 0.121567/),   &
179                                   shape=(/PARASOL_NREFL,PARASOL_NTAU/)),                &
180         ! LUT for ice particles                                     
181         rlumB = reshape(source=(/ 0.03,     0.03,     0.03,     0.03,     0.03,         &
182                                   0.092170, 0.087082, 0.083325, 0.084935, 0.054157,     &
183                                   0.311941, 0.304293, 0.285193, 0.233450, 0.089911,     &
184                                   0.511298, 0.490879, 0.430266, 0.312280, 0.107854,     &
185                                   0.712079, 0.673565, 0.563747, 0.382376, 0.124127,     &
186                                   0.898243, 0.842026, 0.685773, 0.446371, 0.139004,     &
187                                   0.976646, 0.912966, 0.737154, 0.473317, 0.145269/),   &
188                                   shape=(/PARASOL_NREFL,PARASOL_NTAU/)) 
189
190    ! ####################################################################################
191    ! ISCCP simulator tau/CTP joint histogram information
192    ! ####################################################################################
193    integer,parameter :: &
194         numISCCPTauBins  = ntau, &              ! Number of optical depth bins
195         numISCCPPresBins = npres                ! Number of pressure bins     
196    real(wp),parameter,dimension(ntau+1) :: &
197         isccp_histTau = tau_binBounds           ! Joint-histogram boundaries (optical depth)
198    real(wp),parameter,dimension(npres+1) :: &
199         isccp_histPres = pres_binBounds         ! Joint-histogram boundaries (cloud pressure)
200    real(wp),parameter,dimension(ntau) :: &
201         isccp_histTauCenters = tau_binCenters   ! Joint histogram bin centers (optical depth)
202    real(wp),parameter,dimension(npres) :: &   
203         isccp_histPresCenters = pres_binCenters ! Joint histogram bin centers (cloud pressure)
204    real(wp),parameter,dimension(2,ntau) :: &
205         isccp_histTauEdges = tau_binEdges       ! Joint histogram bin edges (optical depth)
206    real(wp),parameter,dimension(2,npres) :: &   
207         isccp_histPresEdges = pres_binEdges     ! Joint histogram bin edges (cloud pressure)   
208   
209    ! ####################################################################################
210    ! MISR simulator tau/CTH joint histogram information
211    ! ####################################################################################
212    integer,parameter ::  &
213         numMISRHgtBins = nhgt, &             ! Number of cloud-top height bins
214         numMISRTauBins = ntau                ! Number of optical depth bins
215    ! Joint histogram boundaries
216    real(wp),parameter,dimension(numMISRHgtBins+1) :: &
217         misr_histHgt = hgt_binBounds         ! Joint-histogram boundaries (cloud height)
218    real(wp),parameter,dimension(numMISRTauBins+1) :: &
219         misr_histTau = tau_binBounds         ! Joint-histogram boundaries (optical-depth)
220    real(wp),parameter,dimension(numMISRHgtBins) :: &
221         misr_histHgtCenters = hgt_binCenters ! Joint-histogram bin centers (cloud height)
222    real(wp),parameter,dimension(2,numMISRHgtBins) :: &
223         misr_histHgtEdges = hgt_BinEdges     ! Joint-histogram bin edges (cloud height)
224 
225    ! ####################################################################################
226    ! MODIS simulator tau/CTP joint histogram information
227    ! ####################################################################################
228    integer,parameter :: &
229         numMODISPresBins = npres                    ! Number of pressure bins for joint-histogram   
230    real(wp),parameter,dimension(numMODISPresBins + 1) :: &
231         modis_histPres = 100*pres_binBounds         ! Joint-histogram boundaries (cloud pressure)
232    real(wp),parameter,dimension(2, numMODISPresBins) :: &
233         modis_histPresEdges = 100*pres_binEdges     ! Joint-histogram bin edges (cloud pressure)
234    real(wp),parameter,dimension(numMODISPresBins) :: &
235         modis_histPresCenters = 100*pres_binCenters ! Joint-histogram bin centers (cloud pressure)
236
237    ! For the MODIS simulator we want to preserve the ability for cospV1.4.0 to use the
238    ! old histogram bin boundaries for optical depth, so these are set up in initialization.
239    integer :: &
240         numMODISTauBins          ! Number of tau bins for joint-histogram
241    real(wp),save,allocatable,dimension(:) :: &
242         modis_histTau            ! Joint-histogram boundaries (optical depth)
243    !$OMP THREADPRIVATE(modis_histTau)
244    real(wp),save,allocatable,dimension(:,:) :: &
245         modis_histTauEdges       ! Joint-histogram bin edges (optical depth)
246    !$OMP THREADPRIVATE(modis_histTauEdges)
247    real(wp),save,allocatable,dimension(:) :: &
248         modis_histTauCenters     ! Joint-histogram bin centers (optical depth)
249    !$OMP THREADPRIVATE(modis_histTauCenters)
250   
251    ! ####################################################################################
252    ! MODIS simulator tau/ReffICE and tau/ReffLIQ joint-histogram information
253    ! ####################################################################################
254    ! Ice
255    integer,parameter :: &
256         numMODISReffIceBins = nReffIce                ! Number of bins for joint-histogram
257    real(wp),parameter,dimension(nReffIce+1) :: &
258         modis_histReffIce = reffICE_binBounds         ! Effective radius bin boundaries
259    real(wp),parameter,dimension(nReffIce) :: &
260         modis_histReffIceCenters = reffICE_binCenters ! Effective radius bin centers
261    real(wp),parameter,dimension(2,nReffICE) :: &
262         modis_histReffIceEdges = reffICE_binEdges     ! Effective radius bin edges
263       
264    ! Liquid
265    integer,parameter :: &
266         numMODISReffLiqBins = nReffLiq                ! Number of bins for joint-histogram
267    real(wp),parameter,dimension(nReffLiq+1) :: &
268         modis_histReffLiq = reffLIQ_binBounds         ! Effective radius bin boundaries
269    real(wp),parameter,dimension(nReffLiq) :: &
270         modis_histReffLiqCenters = reffICE_binCenters ! Effective radius bin centers
271    real(wp),parameter,dimension(2,nReffICE) :: &
272         modis_histReffLiqEdges = reffLIQ_binEdges     ! Effective radius bin edges
273
274    ! ####################################################################################
275    ! CLOUDSAT reflectivity histogram information
276    ! ####################################################################################
277    integer,parameter :: &
278       CLOUDSAT_DBZE_BINS     =   15, & ! Number of dBZe bins in histogram (cfad)
279       CLOUDSAT_DBZE_MIN      = -100, & ! Minimum value for radar reflectivity
280       CLOUDSAT_DBZE_MAX      =   80, & ! Maximum value for radar reflectivity
281       CLOUDSAT_CFAD_ZE_MIN   =  -50, & ! Lower value of the first CFAD Ze bin
282       CLOUDSAT_CFAD_ZE_WIDTH =    5    ! Bin width (dBZe)
283
284    real(wp),parameter,dimension(CLOUDSAT_DBZE_BINS+1) :: &
285         cloudsat_histRef = (/CLOUDSAT_DBZE_MIN,(/(i, i=int(CLOUDSAT_CFAD_ZE_MIN+CLOUDSAT_CFAD_ZE_WIDTH),&
286                             int(CLOUDSAT_CFAD_ZE_MIN+(CLOUDSAT_DBZE_BINS-1)*CLOUDSAT_CFAD_ZE_WIDTH),    &
287                             int(CLOUDSAT_CFAD_ZE_WIDTH))/),CLOUDSAT_DBZE_MAX/)
288    real(wp),parameter,dimension(2,CLOUDSAT_DBZE_BINS) :: &
289         cloudsat_binEdges = reshape(source=(/cloudsat_histRef(1),((cloudsat_histRef(k), &
290                                   l=1,2),k=2,CLOUDSAT_DBZE_BINS),cloudsat_histRef(CLOUDSAT_DBZE_BINS+1)/),&
291                                   shape = (/2,CLOUDSAT_DBZE_BINS/))     
292    real(wp),parameter,dimension(CLOUDSAT_DBZE_BINS) :: &
293         cloudsat_binCenters = (cloudsat_binEdges(1,:)+cloudsat_binEdges(2,:))/2._wp
294   
295    ! Parameters for Cloudsat near-surface precipitation diagnostics.
296    ! Precipitation classes.
297    integer, parameter :: &
298         nCloudsatPrecipClass = 10
299    integer, parameter :: &
300         pClass_noPrecip      = 0, & ! No precipitation
301         pClass_Rain1         = 1, & ! Rain possible
302         pClass_Rain2         = 2, & ! Rain probable
303         pClass_Rain3         = 3, & ! Rain certain
304         pClass_Snow1         = 4, & ! Snow possible
305         pClass_Snow2         = 5, & ! Snow certain
306         pClass_Mixed1        = 6, & ! Mixed-precipitation possible
307         pClass_Mixed2        = 7, & ! Mixed-precipitation certain
308         pClass_Rain4         = 8, & ! Heavy rain
309         pClass_default       = 9    ! Default
310    ! Reflectivity bin boundaries, used by decision tree to classify precipitation type.
311    real(wp), dimension(4),parameter :: &
312         Zenonbinval =(/0._wp, -5._wp, -7.5_wp, -15._wp/)
313    real(wp), dimension(6),parameter :: &
314         Zbinvallnd = (/10._wp, 5._wp, 2.5_wp, -2.5_wp, -5._wp, -15._wp/)
315    ! Vertical level index(Nlvgrid) for Cloudsat precipitation occurence/frequency diagnostics.
316    ! Level 39 of Nlvgrid(40) is 480-960m.
317!    integer, parameter :: &    !PREC_BUG
318!         cloudsat_preclvl = 39 !PREC_BUG
319   
320    ! ####################################################################################
321    ! Parameters used by the CALIPSO LIDAR simulator
322    ! ####################################################################################
323    ! CALISPO backscatter histogram bins
324    real(wp),parameter ::     &
325       S_cld       = 5.0,     & ! Threshold for cloud detection
326       S_att       = 0.01,    & !
327       S_cld_att   = 30.        ! Threshold for undefined cloud phase detection
328    real(wp),parameter,dimension(SR_BINS+1) :: &
329         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,   &
330                              60.0,80.0,999./)         ! Backscatter histogram bins
331    real(wp),parameter,dimension(2,SR_BINS) :: &
332         calipso_binEdges = reshape(source=(/calipso_histBsct(1),((calipso_histBsct(k),  &
333                                    l=1,2),k=2,SR_BINS),calipso_histBsct(SR_BINS+1)/),   &
334                                    shape = (/2,SR_BINS/))     
335    real(wp),parameter,dimension(SR_BINS) :: &
336         calipso_binCenters = (calipso_binEdges(1,:)+calipso_binEdges(2,:))/2._wp 
337
338    integer,parameter  ::     &
339       LIDAR_NTEMP = 40, &
340       LIDAR_NCAT  = 4,  & ! Number of categories for cloudtop heights (high/mid/low/tot)
341       LIDAR_NTYPE = 3     ! Number of categories for OPAQ (opaque/thin cloud + z_opaque)
342    real(wp),parameter,dimension(LIDAR_NTEMP) :: &
343       LIDAR_PHASE_TEMP=                                                                 &
344       (/-91.5,-88.5,-85.5,-82.5,-79.5,-76.5,-73.5,-70.5,-67.5,-64.5,                    &
345         -61.5,-58.5,-55.5,-52.5,-49.5,-46.5,-43.5,-40.5,-37.5,-34.5,                    &
346         -31.5,-28.5,-25.5,-22.5,-19.5,-16.5,-13.5,-10.5, -7.5, -4.5,                    &
347          -1.5,  1.5,  4.5,  7.5, 10.5, 13.5, 16.5, 19.5, 22.5, 25.5/)
348    real(wp),parameter,dimension(2,LIDAR_NTEMP) :: &
349       LIDAR_PHASE_TEMP_BNDS=reshape(source=                                             &
350          (/-273.15, -90., -90., -87., -87., -84., -84., -81., -81., -78.,               &
351             -78.,   -75., -75., -72., -72., -69., -69., -66., -66., -63.,               &
352             -63.,   -60., -60., -57., -57., -54., -54., -51., -51., -48.,               &
353             -48.,   -45., -45., -42., -42., -39., -39., -36., -36., -33.,               &
354             -33.,   -30., -30., -27., -27., -24., -24., -21., -21., -18.,               &
355             -18.,   -15., -15., -12., -12.,  -9.,  -9.,  -6.,  -6.,  -3.,               &
356              -3.,     0.,   0.,   3.,   3.,   6.,   6.,   9.,   9.,  12.,               &
357              12.,    15.,  15.,  18.,  18.,  21.,  21.,  24.,  24., 100. /),            &
358              shape=(/2,40/))       
359
360    ! ####################################################################################
361    ! Parameters used by the GROUND LIDAR simulator
362    ! ####################################################################################
363    ! GROUND LIDAR backscatter histogram bins
364!    real(wp),parameter ::     &
365!       S_cld       = 5.0,     & ! Threshold for cloud detection
366!       S_att       = 0.01,    & !
367!       S_cld_att   = 30.        ! Threshold for undefined cloud phase detection
368    real(wp),parameter,dimension(SR_BINS+1) :: &
369         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,  &
370                                 60.0,80.0,999./)         ! Backscatter histogram bins
371    real(wp),parameter,dimension(2,SR_BINS) :: &
372         grLidar532_binEdges = reshape(source=(/grLidar532_histBsct(1),((grLidar532_histBsct(k),  &
373                                    l=1,2),k=2,SR_BINS),grLidar532_histBsct(SR_BINS+1)/),   &
374                                    shape = (/2,SR_BINS/))     
375    real(wp),parameter,dimension(SR_BINS) :: &
376         grLidar532_binCenters = (grLidar532_binEdges(1,:)+grLidar532_binEdges(2,:))/2._wp 
377
378!    integer,parameter  ::     &
379!       LIDAR_NCAT  = 4       ! Number of categories for cloudtop heights (high/mid/low/tot)
380
381    ! ####################################################################################
382    ! Parameters used by the ATLID LIDAR simulator
383    ! ####################################################################################
384    ! ATLID LIDAR backscatter histogram bins
385    real(wp),parameter ::     &
386       S_cld_atlid       = 1.74,    & ! Threshold for cloud detection
387       S_att_atlid       = 0.01,    & !
388       S_cld_att_atlid   = 6.67        ! Threshold for undefined cloud phase detection
389    real(wp),parameter,dimension(SR_BINS+1) :: &
390         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,  &
391                                 13.2,17.2,999./)         ! Backscatter histogram bins
392    real(wp),parameter,dimension(2,SR_BINS) :: &
393         atlid_binEdges = reshape(source=(/atlid_histBsct(1),((atlid_histBsct(k),  &
394                                    l=1,2),k=2,SR_BINS),atlid_histBsct(SR_BINS+1)/),   &
395                                    shape = (/2,SR_BINS/))     
396    real(wp),parameter,dimension(SR_BINS) :: &
397         atlid_binCenters = (atlid_binEdges(1,:)+atlid_binEdges(2,:))/2._wp 
398
399!    integer,parameter  ::     &
400!       LIDAR_NCAT  = 4       ! Number of categories for cloudtop heights (high/mid/low/tot)
401
402    ! ####################################################################################
403    ! New vertical grid used by CALIPSO and CLOUDSAT L3 (set up during initialization)
404    ! ####################################################################################
405    integer :: &
406         Nlvgrid      ! Number of levels in New grid
407    real(wp),dimension(:), save, allocatable :: &
408       vgrid_zl,  & ! New grid bottoms
409       vgrid_zu,  & ! New grid tops
410       vgrid_z      ! New grid center
411    !$OMP THREADPRIVATE(vgrid_zl,vgrid_zu,vgrid_z)
412
413    ! ####################################################################################
414    ! Vertical grid used by CALIPSO and CLOUDSAT L3 (LMDZ parameter)
415    ! ####################################################################################
416
417    integer, parameter :: &
418         niv_sorties = 40
419    real(wp),parameter,dimension(niv_sorties) :: &
420         vgrid_z_in = (/240.0, 720.0, 1200.0, 1680.0, 2160.0, 2640.0, 3120.0, 3600.0, &
421                        4080.0, 4560.0, 5040.0, 5520.0, 6000.0, 6480.0, 6960.0, 7440.0, &
422                        7920.0, 8400.0, 8880.0, 9360.0, 9840.0, 10320.0, 10800.0, &
423                        11280.0, 11760.0, 12240.0, 12720.0, 13200.0, 13680.0, 14160.0, &
424                        14640.0, 15120.0, 15600.0, 16080.0, 16560.0, 17040.0, 17520.0, &
425                        18000.0, 18480.0, 18960.0/)
426
427END MODULE MOD_COSP_CONFIG
Note: See TracBrowser for help on using the repository browser.