source: LMDZ6/branches/Ocean_skin/libf/phylmd/cosp2/cosp_config.F90 @ 3628

Last change on this file since 3628 was 3396, checked in by idelkadi, 6 years ago

Corrections dans la nouvelle version du simulateur Cosp (cosp2) :

  • Rajout de directives OpenMP pour tourner en mod MPI-OpenMP
  • Correction pour tourner avec Ioipsl
File size: 20.5 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! %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
40
41MODULE MOD_COSP_CONFIG
42    USE COSP_KINDS, ONLY: wp,dp
43    USE mod_phys_lmdz_para
44    IMPLICIT NONE
45
46   ! #####################################################################################
47   ! Common COSP information
48   ! #####################################################################################
49    character(len=32) ::   &
50         COSP_VERSION              ! COSP Version ID (set in cosp_interface_init)
51    real(wp),parameter ::  &
52         R_UNDEF      = -1.0E30, & ! Missing value
53         R_GROUND     = -1.0E20, & ! Flag for below ground results
54         scops_ccfrac = 0.05       ! Fraction of column (or subcolumn) covered with convective
55                                   ! precipitation (default is 5%). *NOTE* This quantity may vary
56                                   ! between modeling centers.
57    logical :: &
58         use_vgrid                 ! True=Use new grid for L3 CLOUDAT and CALIPSO
59    integer,parameter ::   &
60         SR_BINS = 15,           & ! Number of bins (backscattering coefficient) in CALOPSO LIDAR simulator.
61         N_HYDRO = 9               ! Number of hydrometeor classes used by quickbeam radar simulator.
62
63    ! #################################################################################### 
64    ! Joint histogram bin-boundaries
65    ! tau is used by ISCCP and MISR
66    ! pres is used by ISCCP
67    ! hgt is used by MISR
68    ! ReffLiq is used by MODIS
69    ! ReffIce is used by MODIS
70    ! *NOTE* ALL JOINT-HISTOGRAM BIN BOUNDARIES ARE DECLARED AND DEFINED HERE IN
71    !        COSP_CONFIG, WITH THE EXCEPTION OF THE TAU AXIS USED BY THE MODIS SIMULATOR,
72    !        WHICH IS SET DURING INITIALIZATION IN COSP_INTERFACE_INIT.
73    ! ####################################################################################
74    ! Optical depth bin axis
75    integer,parameter :: &
76         ntau=7 
77    real(wp),parameter,dimension(ntau+1) :: &
78       tau_binBounds = (/0.0, 0.3, 1.3, 3.6, 9.4, 23., 60., 10000./)
79    real(wp),parameter,dimension(ntau) :: &
80         tau_binCenters = (/0.15, 0.80, 2.45, 6.5, 16.2, 41.5, 100.0/)
81    real(wp),parameter,dimension(2,ntau) :: &
82         tau_binEdges = reshape(source=(/0.0, 0.3,  0.3,  1.3,  1.3,  3.6,      3.6,     &
83                                         9.4, 9.4, 23.0, 23.0, 60.0, 60.0, 100000.0/),   &
84                                         shape=(/2,ntau/))
85
86    ! Optical depth bin axes (ONLY USED BY MODIS SIMULATOR IN v1.4)
87    integer :: l,k
88    integer,parameter :: &
89         ntauV1p4 = 6
90    real(wp),parameter,dimension(ntauV1p4+1) :: &
91         tau_binBoundsV1p4 = (/0.3, 1.3, 3.6, 9.4, 23., 60., 10000./)
92    real(wp),parameter,dimension(2,ntauV1p4) :: &
93         tau_binEdgesV1p4 = reshape(source =(/tau_binBoundsV1p4(1),((tau_binBoundsV1p4(k),l=1,2),   &
94                                             k=2,ntauV1p4),100000._wp/),shape = (/2,ntauV1p4/))
95    real(wp),parameter,dimension(ntauV1p4) :: &
96         tau_binCentersV1p4 = (tau_binEdgesV1p4(1,:)+tau_binEdgesV1p4(2,:))/2._wp 
97   
98    ! Cloud-top height pressure bin axis
99    integer,parameter :: &
100         npres = 7     
101    real(wp),parameter,dimension(npres+1) :: &
102         pres_binBounds = (/0., 180., 310., 440., 560., 680., 800., 10000./)
103    real(wp),parameter,dimension(npres) :: &
104         pres_binCenters = (/90000., 74000., 62000., 50000., 37500., 24500., 9000./)   
105    real(wp),parameter,dimension(2,npres) :: &
106         pres_binEdges = reshape(source=(/100000.0, 80000.0, 80000.0, 68000.0, 68000.0,    &
107                                           56000.0, 56000.0, 44000.0, 44000.0, 31000.0,    &
108                                           31000.0, 18000.0, 18000.0,     0.0/),           &
109                                           shape=(/2,npres/))
110
111    ! Cloud-top height bin axis #1
112    integer,parameter :: &
113         nhgt = 16
114    real(wp),parameter,dimension(nhgt+1) :: &
115         hgt_binBounds = (/-.99,0.,0.5,1.,1.5,2.,2.5,3.,4.,5.,7.,9.,11.,13.,15.,17.,99./)
116    real(wp),parameter,dimension(nhgt) :: &
117         hgt_binCenters = 1000*(/0.,0.25,0.75,1.25,1.75,2.25,2.75,3.5,4.5,6.,8.,10.,12.,   &
118         14.5,16.,18./) 
119    real(wp),parameter,dimension(2,nhgt) :: &
120         hgt_binEdges = 1000.0*reshape(source=(/-99.0, 0.0, 0.0, 0.5, 0.5, 1.0, 1.0, 1.5,  &
121                                                  1.5, 2.0, 2.0, 2.5, 2.5, 3.0, 3.0, 4.0,  &
122                                                  4.0, 5.0, 5.0, 7.0, 7.0, 9.0, 9.0,11.0,  &
123                                                  11.0,13.0,13.0,15.0,15.0,17.0,17.0,99.0/),&
124                                                  shape=(/2,nhgt/))   
125
126    ! Liquid and Ice particle bins for MODIS joint histogram of optical-depth and particle
127    ! size
128    integer :: i,j
129    integer,parameter :: &
130         nReffLiq = 6, & ! Number of bins for tau/ReffLiq joint-histogram
131         nReffIce = 6    ! Number of bins for tau/ReffICE joint-histogram
132    real(wp),parameter,dimension(nReffLiq+1) :: &
133         reffLIQ_binBounds = (/0., 8e-6, 1.0e-5, 1.3e-5, 1.5e-5, 2.0e-5, 3.0e-5/)
134    real(wp),parameter,dimension(nReffIce+1) :: &
135         reffICE_binBounds = (/0., 1.0e-5, 2.0e-5, 3.0e-5, 4.0e-5, 6.0e-5, 9.0e-5/)
136    real(wp),parameter,dimension(2,nReffICE) :: &
137         reffICE_binEdges = reshape(source=(/reffICE_binBounds(1),((reffICE_binBounds(k),  &
138                                    l=1,2),k=2,nReffICE),reffICE_binBounds(nReffICE+1)/),  &
139                                    shape = (/2,nReffICE/))
140    real(wp),parameter,dimension(2,nReffLIQ) :: &
141         reffLIQ_binEdges = reshape(source=(/reffLIQ_binBounds(1),((reffLIQ_binBounds(k),  &
142                                    l=1,2),k=2,nReffLIQ),reffLIQ_binBounds(nReffICE+1)/),  &
143                                    shape = (/2,nReffLIQ/))             
144    real(wp),parameter,dimension(nReffICE) :: &
145         reffICE_binCenters = (reffICE_binEdges(1,:)+reffICE_binEdges(2,:))/2._wp
146    real(wp),parameter,dimension(nReffLIQ) :: &
147         reffLIQ_binCenters = (reffLIQ_binEdges(1,:)+reffLIQ_binEdges(2,:))/2._wp
148
149    ! #################################################################################### 
150    ! Constants used by RTTOV.
151    ! #################################################################################### 
152    integer,parameter :: &
153         RTTOV_MAX_CHANNELS = 20
154    character(len=256),parameter :: &
155         rttovDir = '/Projects/Clouds/dswales/RTTOV/rttov_11.3/'
156   
157    ! #################################################################################### 
158    ! Constants used by the PARASOL simulator.
159    ! #################################################################################### 
160    integer,parameter :: &
161         PARASOL_NREFL = 5,  & ! Number of angles in LUT
162         PARASOL_NTAU  = 7     ! Number of optical depths in LUT
163    real(wp),parameter,dimension(PARASOL_NREFL) :: &
164         PARASOL_SZA = (/0.0, 20.0, 40.0, 60.0, 80.0/)
165    REAL(WP),parameter,dimension(PARASOL_NTAU) :: &
166         PARASOL_TAU = (/0., 1., 5., 10., 20., 50., 100./)
167   
168    ! LUTs
169    REAL(WP),parameter,dimension(PARASOL_NREFL,PARASOL_NTAU) :: &
170         ! LUT for liquid particles
171         rlumA = reshape(source=(/ 0.03,     0.03,     0.03,     0.03,     0.03,         &
172                                   0.090886, 0.072185, 0.058410, 0.052498, 0.034730,     &
173                                   0.283965, 0.252596, 0.224707, 0.175844, 0.064488,     &
174                                   0.480587, 0.436401, 0.367451, 0.252916, 0.081667,     &
175                                   0.695235, 0.631352, 0.509180, 0.326551, 0.098215,     &
176                                   0.908229, 0.823924, 0.648152, 0.398581, 0.114411,     &
177                                   1.0,      0.909013, 0.709554, 0.430405, 0.121567/),   &
178                                   shape=(/PARASOL_NREFL,PARASOL_NTAU/)),                &
179         ! LUT for ice particles                                     
180         rlumB = reshape(source=(/ 0.03,     0.03,     0.03,     0.03,     0.03,         &
181                                   0.092170, 0.087082, 0.083325, 0.084935, 0.054157,     &
182                                   0.311941, 0.304293, 0.285193, 0.233450, 0.089911,     &
183                                   0.511298, 0.490879, 0.430266, 0.312280, 0.107854,     &
184                                   0.712079, 0.673565, 0.563747, 0.382376, 0.124127,     &
185                                   0.898243, 0.842026, 0.685773, 0.446371, 0.139004,     &
186                                   0.976646, 0.912966, 0.737154, 0.473317, 0.145269/),   &
187                                   shape=(/PARASOL_NREFL,PARASOL_NTAU/)) 
188
189    ! ####################################################################################
190    ! ISCCP simulator tau/CTP joint histogram information
191    ! ####################################################################################
192    integer,parameter :: &
193         numISCCPTauBins  = ntau, &              ! Number of optical depth bins
194         numISCCPPresBins = npres                ! Number of pressure bins     
195    real(wp),parameter,dimension(ntau+1) :: &
196         isccp_histTau = tau_binBounds           ! Joint-histogram boundaries (optical depth)
197    real(wp),parameter,dimension(npres+1) :: &
198         isccp_histPres = pres_binBounds         ! Joint-histogram boundaries (cloud pressure)
199    real(wp),parameter,dimension(ntau) :: &
200         isccp_histTauCenters = tau_binCenters   ! Joint histogram bin centers (optical depth)
201    real(wp),parameter,dimension(npres) :: &   
202         isccp_histPresCenters = pres_binCenters ! Joint histogram bin centers (cloud pressure)
203    real(wp),parameter,dimension(2,ntau) :: &
204         isccp_histTauEdges = tau_binEdges       ! Joint histogram bin edges (optical depth)
205    real(wp),parameter,dimension(2,npres) :: &   
206         isccp_histPresEdges = pres_binEdges     ! Joint histogram bin edges (cloud pressure)   
207   
208    ! ####################################################################################
209    ! MISR simulator tau/CTH joint histogram information
210    ! ####################################################################################
211    integer,parameter ::  &
212         numMISRHgtBins = nhgt, &             ! Number of cloud-top height bins
213         numMISRTauBins = ntau                ! Number of optical depth bins
214    ! Joint histogram boundaries
215    real(wp),parameter,dimension(numMISRHgtBins+1) :: &
216         misr_histHgt = hgt_binBounds         ! Joint-histogram boundaries (cloud height)
217    real(wp),parameter,dimension(numMISRTauBins+1) :: &
218         misr_histTau = tau_binBounds         ! Joint-histogram boundaries (optical-depth)
219    real(wp),parameter,dimension(numMISRHgtBins) :: &
220         misr_histHgtCenters = hgt_binCenters ! Joint-histogram bin centers (cloud height)
221    real(wp),parameter,dimension(2,numMISRHgtBins) :: &
222         misr_histHgtEdges = hgt_BinEdges     ! Joint-histogram bin edges (cloud height)
223 
224    ! ####################################################################################
225    ! MODIS simulator tau/CTP joint histogram information
226    ! ####################################################################################
227    integer,parameter :: &
228         numMODISPresBins = npres                    ! Number of pressure bins for joint-histogram   
229    real(wp),parameter,dimension(numMODISPresBins + 1) :: &
230         modis_histPres = 100*pres_binBounds         ! Joint-histogram boundaries (cloud pressure)
231    real(wp),parameter,dimension(2, numMODISPresBins) :: &
232         modis_histPresEdges = 100*pres_binEdges     ! Joint-histogram bin edges (cloud pressure)
233    real(wp),parameter,dimension(numMODISPresBins) :: &
234         modis_histPresCenters = 100*pres_binCenters ! Joint-histogram bin centers (cloud pressure)
235
236    ! For the MODIS simulator we want to preserve the ability for cospV1.4.0 to use the
237    ! old histogram bin boundaries for optical depth, so these are set up in initialization.
238    integer :: &
239         numMODISTauBins          ! Number of tau bins for joint-histogram
240    real(wp),save,allocatable,dimension(:) :: &
241         modis_histTau            ! Joint-histogram boundaries (optical depth)
242    !$OMP THREADPRIVATE(modis_histTau)
243    real(wp),save,allocatable,dimension(:,:) :: &
244         modis_histTauEdges       ! Joint-histogram bin edges (optical depth)
245    !$OMP THREADPRIVATE(modis_histTauEdges)
246    real(wp),save,allocatable,dimension(:) :: &
247         modis_histTauCenters     ! Joint-histogram bin centers (optical depth)
248    !$OMP THREADPRIVATE(modis_histTauCenters)
249    ! ####################################################################################
250    ! MODIS simulator tau/ReffICE and tau/ReffLIQ joint-histogram information
251    ! ####################################################################################
252    ! Ice
253    integer,parameter :: &
254         numMODISReffIceBins = nReffIce                ! Number of bins for joint-histogram
255    real(wp),parameter,dimension(nReffIce+1) :: &
256         modis_histReffIce = reffICE_binBounds         ! Effective radius bin boundaries
257    real(wp),parameter,dimension(nReffIce) :: &
258         modis_histReffIceCenters = reffICE_binCenters ! Effective radius bin centers
259    real(wp),parameter,dimension(2,nReffICE) :: &
260         modis_histReffIceEdges = reffICE_binEdges     ! Effective radius bin edges
261       
262    ! Liquid
263    integer,parameter :: &
264         numMODISReffLiqBins = nReffLiq                ! Number of bins for joint-histogram
265    real(wp),parameter,dimension(nReffLiq+1) :: &
266         modis_histReffLiq = reffLIQ_binBounds         ! Effective radius bin boundaries
267    real(wp),parameter,dimension(nReffLiq) :: &
268         modis_histReffLiqCenters = reffICE_binCenters ! Effective radius bin centers
269    real(wp),parameter,dimension(2,nReffICE) :: &
270         modis_histReffLiqEdges = reffLIQ_binEdges     ! Effective radius bin edges
271
272    ! ####################################################################################
273    ! CLOUDSAT reflectivity histogram information
274    ! ####################################################################################
275    integer,parameter :: &
276       DBZE_BINS     =   15, & ! Number of dBZe bins in histogram (cfad)
277       DBZE_MIN      = -100, & ! Minimum value for radar reflectivity
278       DBZE_MAX      =   80, & ! Maximum value for radar reflectivity
279       CFAD_ZE_MIN   =  -50, & ! Lower value of the first CFAD Ze bin
280       CFAD_ZE_WIDTH =    5    ! Bin width (dBZe)
281
282    real(wp),parameter,dimension(DBZE_BINS+1) :: &
283         cloudsat_histRef = (/DBZE_MIN,(/(i, i=int(CFAD_ZE_MIN+CFAD_ZE_WIDTH),           &
284                             int(CFAD_ZE_MIN+(DBZE_BINS-1)*CFAD_ZE_WIDTH),               &
285                             int(CFAD_ZE_WIDTH))/),DBZE_MAX/)
286    real(wp),parameter,dimension(2,DBZE_BINS) :: &
287         cloudsat_binEdges = reshape(source=(/cloudsat_histRef(1),((cloudsat_histRef(k), &
288                                   l=1,2),k=2,DBZE_BINS),cloudsat_histRef(DBZE_BINS+1)/),&
289                                   shape = (/2,DBZE_BINS/))     
290    real(wp),parameter,dimension(DBZE_BINS) :: &
291         cloudsat_binCenters = (cloudsat_binEdges(1,:)+cloudsat_binEdges(2,:))/2._wp 
292
293    ! ####################################################################################
294    ! Parameters used by the CALIPSO LIDAR simulator
295    ! ####################################################################################
296    ! CALISPO backscatter histogram bins
297    real(wp),parameter ::     &
298       S_cld       = 5.0,     & ! Threshold for cloud detection
299       S_att       = 0.01,    & !
300       S_cld_att   = 30.        ! Threshold for undefined cloud phase detection
301    real(wp),parameter,dimension(SR_BINS+1) :: &
302         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,   &
303                              60.0,80.0,999./)         ! Backscatter histogram bins
304    real(wp),parameter,dimension(2,SR_BINS) :: &
305         calipso_binEdges = reshape(source=(/calipso_histBsct(1),((calipso_histBsct(k),  &
306                                    l=1,2),k=2,SR_BINS),calipso_histBsct(SR_BINS+1)/),   &
307                                    shape = (/2,SR_BINS/))     
308    real(wp),parameter,dimension(SR_BINS) :: &
309         calipso_binCenters = (calipso_binEdges(1,:)+calipso_binEdges(2,:))/2._wp 
310
311    integer,parameter  ::     &
312       LIDAR_NTEMP = 40, &
313       LIDAR_NCAT  = 4     ! Number of categories for cloudtop heights (high/mid/low/tot)
314    real(wp),parameter,dimension(LIDAR_NTEMP) :: &
315       LIDAR_PHASE_TEMP=                                                                 &
316       (/-91.5,-88.5,-85.5,-82.5,-79.5,-76.5,-73.5,-70.5,-67.5,-64.5,                    &
317         -61.5,-58.5,-55.5,-52.5,-49.5,-46.5,-43.5,-40.5,-37.5,-34.5,                    &
318         -31.5,-28.5,-25.5,-22.5,-19.5,-16.5,-13.5,-10.5, -7.5, -4.5,                    &
319          -1.5,  1.5,  4.5,  7.5, 10.5, 13.5, 16.5, 19.5, 22.5, 25.5/)
320    real(wp),parameter,dimension(2,LIDAR_NTEMP) :: &
321       LIDAR_PHASE_TEMP_BNDS=reshape(source=                                             &
322          (/-273.15, -90., -90., -87., -87., -84., -84., -81., -81., -78.,               &
323             -78.,   -75., -75., -72., -72., -69., -69., -66., -66., -63.,               &
324             -63.,   -60., -60., -57., -57., -54., -54., -51., -51., -48.,               &
325             -48.,   -45., -45., -42., -42., -39., -39., -36., -36., -33.,               &
326             -33.,   -30., -30., -27., -27., -24., -24., -21., -21., -18.,               &
327             -18.,   -15., -15., -12., -12.,  -9.,  -9.,  -6.,  -6.,  -3.,               &
328              -3.,     0.,   0.,   3.,   3.,   6.,   6.,   9.,   9.,  12.,               &
329              12.,    15.,  15.,  18.,  18.,  21.,  21.,  24.,  24., 100. /),            &
330              shape=(/2,40/))       
331
332    ! ####################################################################################
333    ! New vertical grid used by CALIPSO and CLOUDSAT L3 (set up during initialization)
334    ! ####################################################################################
335    integer :: &
336         Nlvgrid      ! Number of levels in New grid
337!    real(wp),dimension(:),allocatable,save : &
338!       vgrid_zl,  & ! New grid bottoms
339!       vgrid_zu,  & ! New grid tops
340!       vgrid_z      ! New grid center
341    REAL(wp), SAVE, ALLOCATABLE :: vgrid_zl(:),vgrid_zu(:),vgrid_z(:)
342    !$OMP THREADPRIVATE(vgrid_zl,vgrid_zu,vgrid_z)
343END MODULE MOD_COSP_CONFIG
Note: See TracBrowser for help on using the repository browser.