Ignore:
Timestamp:
Jan 27, 2016, 10:42:32 AM (8 years ago)
Author:
idelkadi
Message:

Mise a jour du simulateur COSP (passage de la version v3.2 a la version v1.4) :

  • mise a jour des sources pour ISCCP, CALIPSO et PARASOL
  • prise en compte des changements de phases pour les nuages (Calipso)
  • rajout de plusieurs diagnostiques (fraction nuageuse en fonction de la temperature, ...)

http://lmdz.lmd.jussieu.fr/Members/aidelkadi/cosp

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/cosp/cosp_constants.F90

    r2080 r2428  
    2828! Jul 2008 - A. Bodas-Salcedo - Added definitions of ISCCP axes
    2929! Oct 2008 - H. Chepfer       - Added PARASOL_NREFL
     30! Jun 2010 - R. Marchand      - Modified to support quickbeam V3, added ifdef for hydrometeor definitions
     31!
    3032!
    3133!
     34
     35#include "cosp_defs.h"
    3236MODULE MOD_COSP_CONSTANTS
     37
    3338    use netcdf, only: nf90_fill_real
    3439    IMPLICIT NONE
    35    
     40
     41    character(len=32) :: COSP_VERSION='COSP v1.4'
     42
    3643    ! Indices to address arrays of LS and CONV hydrometeors
    3744    integer,parameter :: I_LSCLIQ = 1
     
    4451    integer,parameter :: I_CVSNOW = 8
    4552    integer,parameter :: I_LSGRPL = 9
    46    
     53
    4754    ! Missing value
    48 !!    real,parameter :: R_UNDEF = -1.0E30
    49 !     real,parameter :: R_UNDEF = 9.96921e+36
    50       real,parameter :: R_UNDEF = nf90_fill_real
     55    real,parameter :: R_UNDEF = -1.0E30
     56!    real,parameter :: R_UNDEF = nf90_fill_real
    5157
    5258    ! Number of possible output variables
    53     integer,parameter :: N_OUT_LIST = 27
     59    integer,parameter :: N_OUT_LIST = 63
     60    integer,parameter :: N3D = 8
     61    integer,parameter :: N2D = 14
     62    integer,parameter :: N1D = 40
     63
    5464    ! Value for forward model result from a level that is under the ground
    5565    real,parameter :: R_GROUND = -1.0E20
     
    5868    integer, parameter :: I_LSC = 1, & ! Large-scale clouds
    5969                          I_CVC = 2    ! Convective clouds
    60    
     70
     71    ! Timing of different simulators, including statistics module
     72    integer, parameter :: N_SIMULATORS = 7
     73    integer,parameter :: I_RADAR = 1
     74    integer,parameter :: I_LIDAR = 2
     75    integer,parameter :: I_ISCCP = 3
     76    integer,parameter :: I_MISR  = 4
     77    integer,parameter :: I_MODIS = 5
     78    integer,parameter :: I_RTTOV = 6
     79    integer,parameter :: I_STATS = 7
     80    character*32, dimension(N_SIMULATORS) :: SIM_NAME = (/'Radar','Lidar','ISCCP','MISR ','MODIS','RTTOV','Stats'/)
     81    integer,dimension(N_SIMULATORS) :: tsim
     82    data tsim/N_SIMULATORS*0.0/
     83
    6184    !--- Radar constants
    6285    ! CFAD constants
     
    6790    real,parameter    :: CFAD_ZE_WIDTH =    5.0 ! Bin width (dBZe)
    6891
    69    
     92
    7093    !--- Lidar constants
    7194    ! CFAD constants
     
    7396    integer,parameter :: DPOL_BINS     =   6
    7497    real,parameter    :: LIDAR_UNDEF   =   999.999
     98
    7599    ! Other constants
    76100    integer,parameter :: LIDAR_NCAT    =   4
    77101    integer,parameter :: PARASOL_NREFL =   5 ! parasol
    78     real,parameter,dimension(PARASOL_NREFL) :: PARASOL_SZA = (/0.0, 20.0, 40.0, 6.0, 80.0/)
    79 !    real,parameter,dimension(PARASOL_NREFL) :: PARASOL_SZA = (/1.0, 2.0, 3.0, 4.0, 5.0/)
     102    real,parameter,dimension(PARASOL_NREFL) :: PARASOL_SZA = (/0.0, 20.0, 40.0, 60.0, 80.0/)
    80103    real,parameter    :: DEFAULT_LIDAR_REFF = 30.0e-6 ! Default lidar effective radius
    81    
     104
     105    integer,parameter :: LIDAR_NTEMP = 40
     106    real,parameter,dimension(LIDAR_NTEMP) :: LIDAR_PHASE_TEMP=(/-91.5,-88.5,-85.5,-82.5,-79.5,-76.5,-73.5,-70.5,-67.5,-64.5, &
     107                   -61.5,-58.5,-55.5,-52.5,-49.5,-46.5,-43.5,-40.5,-37.5,-34.5, &
     108                   -31.5,-28.5,-25.5,-22.5,-19.5,-16.5,-13.5,-10.5, -7.5, -4.5, &
     109                    -1.5,  1.5,  4.5,  7.5, 10.5, 13.5, 16.5, 19.5, 22.5, 25.5/)
     110    real,parameter,dimension(2,LIDAR_NTEMP) :: LIDAR_PHASE_TEMP_BNDS=reshape(source=(/-273.15,-90.,-90.,-87.,-87.,-84.,-84.,-81.,-81.,-78., &
     111                   -78.,-75.,-75.,-72.,-72.,-69.,-69.,-66.,-66.,-63., &
     112                   -63.,-60.,-60.,-57.,-57.,-54.,-54.,-51.,-51.,-48., &
     113                   -48.,-45.,-45.,-42.,-42.,-39.,-39.,-36.,-36.,-33., &
     114                   -33.,-30.,-30.,-27.,-27.,-24.,-24.,-21.,-21.,-18., &
     115                   -18.,-15.,-15.,-12.,-12., -9., -9., -6., -6., -3., &
     116                    -3.,  0.,  0.,  3.,  3.,  6.,  6.,  9.,  9., 12., &
     117                    12., 15., 15., 18., 18., 21., 21., 24., 24.,100./),shape=(/2,40/))
     118
    82119    !--- MISR constants
    83120    integer,parameter :: MISR_N_CTH = 16
     
    85122    !--- RTTOV constants
    86123    integer,parameter :: RTTOV_MAX_CHANNELS = 20
    87    
     124
    88125    ! ISCCP tau-Pc axes
    89     real,parameter,dimension(7) :: ISCCP_TAU = (/0.15, 0.80, 2.45, 6.5, 16.2, 41.5, 50000.0/)
     126    real,parameter,dimension(7) :: ISCCP_TAU = (/0.15, 0.80, 2.45, 6.5, 16.2, 41.5, 100.0/)
    90127    real,parameter,dimension(2,7) :: ISCCP_TAU_BNDS = reshape(source=(/0.0,0.3,0.3,1.30,1.30,3.6,3.6,9.4, &
    91128                                                      9.4,23.0,23.0,60.0,60.0,100000.0/), shape=(/2,7/))
    92    
    93 !     real,parameter,dimension(7) :: ISCCP_PC = (/9000., 24500., 37500., 50000., 62000., 74000., 90000./)
    94 !     real,parameter,dimension(2,7) :: ISCCP_PC_BNDS = reshape(source=(/0.0,18000.0,18000.0,31000.0,31000.0, &
    95 !                                44000.0,44000.0,56000.0,56000.0,68000.0,68000.0,80000.0,80000.0,100000.0/), shape=(/2,7/))
    96    
     129
    97130    real,parameter,dimension(7) :: ISCCP_PC = (/90000., 74000., 62000., 50000., 37500., 24500., 9000./)
    98131    real,parameter,dimension(2,7) :: ISCCP_PC_BNDS = reshape(source=(/100000.0,80000.0,80000.0,68000.0,68000.0,56000.0 &
    99132                               ,56000.0,44000.0,44000.0,31000.0,31000.0,18000.0,18000.0,0.0/), shape=(/2,7/))
    100    
    101     real,parameter,dimension(MISR_N_CTH) :: MISR_CTH = (/ 0., 0.25, 0.75, 1.25, 1.75, 2.25, 2.75, 3.5, &
     133
     134    real,parameter,dimension(MISR_N_CTH) :: MISR_CTH = 1000.0*(/ 0., 0.25, 0.75, 1.25, 1.75, 2.25, 2.75, 3.5, &
    102135                                            4.5, 6., 8., 10., 12., 14.5, 16., 18./)
    103     real,parameter,dimension(2,MISR_N_CTH) :: MISR_CTH_BNDS = reshape(source=(/ &
     136    real,parameter,dimension(2,MISR_N_CTH) :: MISR_CTH_BNDS = 1000.0*reshape(source=(/ &
    104137                                            -99.0,  0.0,       0.0,  0.5,       0.5,  1.0,      1.0,  1.5, &
    105138                                              1.5,  2.0,       2.0,  2.5,       2.5,  3.0,      3.0,  4.0, &
     
    107140                                             11.0, 13.0,      13.0, 15.0,      15.0, 17.0,     17.0, 99.0/), &
    108141                                             shape=(/2,MISR_N_CTH/))
    109            
    110     !  Table hclass for quickbeam
     142
     143
     144    !
     145    ! The following code was modifed by Roj with implementation of quickbeam V3
     146    !   (1) use ifdef to support more than one microphyscis scheme
     147    !   (2) added constants  microphysic_scheme_name, LOAD_scale_LUTs, and SAVE_scale_LUTs
     148    !
     149
     150    ! directory where LUTs will be stored
     151    character*120 :: RADAR_SIM_LUT_DIRECTORY = './'
     152
     153#ifdef MMF_V3_SINGLE_MOMENT
     154
     155    !       
     156    !  Table hclass for quickbeam to support one-moment (bulk) microphysics scheme used by MMF V3.0 & V3.5
     157    !
     158
     159    !
     160    ! NOTE:  if ANY value in this section of code is changed, the existing LUT
     161    !        (i.e., the associated *.dat file) MUST be deleted so that a NEW
     162    !        LUT will be created !!!
     163    !
     164    character*120 :: RADAR_SIM_MICROPHYSICS_SCHEME_NAME = 'MMF_v3_single_moment'
     165
     166    logical :: RADAR_SIM_LOAD_scale_LUTs_flag   = .false.
     167    logical :: RADAR_SIM_UPDATE_scale_LUTs_flag = .false.
    111168    integer,parameter :: N_HYDRO = 9
    112     real :: HCLASS_TYPE(N_HYDRO),HCLASS_COL(N_HYDRO),HCLASS_PHASE(N_HYDRO), &
    113             HCLASS_CP(N_HYDRO),HCLASS_DMIN(N_HYDRO),HCLASS_DMAX(N_HYDRO)
    114     real :: HCLASS_APM(N_HYDRO),HCLASS_BPM(N_HYDRO),HCLASS_RHO(N_HYDRO), &
     169
     170    integer :: HCLASS_TYPE(N_HYDRO),HCLASS_PHASE(N_HYDRO)
     171
     172    real :: HCLASS_DMIN(N_HYDRO),HCLASS_DMAX(N_HYDRO), &
     173            HCLASS_APM(N_HYDRO),HCLASS_BPM(N_HYDRO),HCLASS_RHO(N_HYDRO), &
    115174            HCLASS_P1(N_HYDRO),HCLASS_P2(N_HYDRO),HCLASS_P3(N_HYDRO)
    116     data HCLASS_TYPE/5,1,2,2,5,1,2,2,2/
    117     data HCLASS_COL/1,2,3,4,5,6,7,8,9/
    118     data HCLASS_PHASE/0,1,0,1,0,1,0,1,1/
    119     data HCLASS_CP/0,0,1,1,0,0,1,1,1/
    120     data HCLASS_DMIN/-1,-1,-1,-1,-1,-1,-1,-1,-1/
    121     data HCLASS_DMAX/-1,-1,-1,-1,-1,-1,-1,-1,-1/
    122     data HCLASS_APM/524,110.8,524,-1,524,110.8,524,-1,-1/
    123     data HCLASS_BPM/3,2.91,3,-1,3,2.91,3,-1,-1/
    124     data HCLASS_RHO/-1,-1,-1,100,-1,-1,-1,100,400/
    125     data HCLASS_P1/-1,-1,8000000.,3000000.,-1,-1,8000000.,3000000.,4000000./
    126     data HCLASS_P2/6,40,-1,-1,6,40,-1,-1,-1/
    127     data HCLASS_P3/0.3,2,-1,-1,0.3,2,-1,-1,-1/
    128 
    129    
    130    
     175
     176    ! HCLASS_CP is not used in the version of Quickbeam included in COSP
     177    !                   LSL    LSI      LSR     LSS   CVL    CVI   CVR     CVS   LSG
     178    data HCLASS_TYPE/    5,      1,      2,      2,     5,     1,   2,      2,    2/
     179    data HCLASS_PHASE/   0,      1,      0,      1,     0,     1,   0,      1,    1/
     180    data HCLASS_DMIN/   -1,     -1,     -1,     -1,    -1,    -1,   -1,    -1,   -1/
     181    data HCLASS_DMAX/   -1,     -1,     -1,     -1,    -1,    -1,   -1,    -1,   -1/
     182    data HCLASS_APM/   524,  110.8,    524,     -1,   524, 110.8,  524,    -1,   -1/
     183    data HCLASS_BPM/     3,   2.91,      3,     -1,     3,  2.91,    3,    -1,   -1/
     184    data HCLASS_RHO/    -1,     -1,     -1,    100,    -1,    -1,   -1,   100,  400/
     185    data HCLASS_P1/     -1,     -1,   8.e6,   3.e6,    -1,    -1, 8.e6,  3.e6, 4.e6/
     186    data HCLASS_P2/      6,     40,     -1,      -1,    6,    40,   -1,    -1,   -1/
     187    data HCLASS_P3/    0.3,      2,     -1,      -1,  0.3,     2,   -1,    -1,   -1/
     188
     189    ! NOTES on HCLASS variables
     190    !
     191    ! TYPE - Set to
     192    ! 1 for modified gamma distribution,
     193    ! 2 for exponential distribution,
     194    ! 3 for power law distribution,
     195    ! 4 for monodisperse distribution,
     196    ! 5 for lognormal distribution.
     197
     198    ! PHASE - Set to 0 for liquid, 1 for ice.
     199
     200    ! DMIN - The minimum drop size for this class (micron), ignored for monodisperse.
     201    ! DMAX - The maximum drop size for this class (micron), ignored for monodisperse.
     202    ! Important note: The settings for DMIN and DMAX are
     203    ! ignored in the current version for all distributions except for power
     204    ! law. Except when the power law distribution is used, particle size
     205    ! is fixed to vary from zero to infinity, a restriction that is expected
     206    ! to be lifted in future versions. A placeholder must still be specified
     207    ! for each.
     208
     209    ! Density of particles is given by apm*D^bpm or a fixed value rho. ONLY specify ONE of these two!!
     210    ! APM - The alpha_m coefficient in equation (1) (kg m**-beta_m )
     211    ! BPM - The beta_m coefficient in equation (1), see section 4.1.
     212
     213    ! RHO - Hydrometeor density (kg m-3 ).
     214
     215    ! P1, P2, P3 - are default distribution parameters that depend on the type
     216    ! of distribution (see quickmbeam documentation for more information)
     217    !
     218    ! Modified Gamma (must set P3 and one of P1 or P2)
     219    ! P1 - Set to the total particle number concentration Nt /rho_a (kg-1 ), where
     220    ! rho_a is the density of air in the radar volume.
     221    ! P2 - Set to the particle mean diameter D (micron).
     222    ! P3 - Set to the distribution width nu.
     223    !
     224    ! Exponetial (set one of)
     225    ! P1 - Set to a constant intercept parameter N0 (m-4).
     226    ! P2 - Set to a constant lambda (micron-1).
     227    !
     228    ! Power Law
     229    ! P1 - Set this to the value of a constant power law parameter br
     230    !
     231    ! Monodisperse
     232    ! P1 - Set to a constant diameter D0 (micron) = Re.
     233    !
     234    ! Log-normal (must set P3 and one of P1 or P2)
     235    ! P1 - Set to the total particle number concentration Nt /rho_a (kg-1 )
     236    ! P2 - Set to the geometric mean particle radius rg (micron).
     237    ! P3 - Set to the natural logarithm of the geometric standard deviation.
     238    !
     239
     240
     241    real,dimension(N_HYDRO) :: N_ax,N_bx,alpha_x,c_x,d_x,g_x,a_x,b_x,gamma_1,gamma_2,gamma_3,gamma_4
     242
     243    ! Microphysical settings for the precipitation flux to mixing ratio conversion
     244    !                LSL    LSI       LSR       LSS   CVL    CVI       CVR       CVS      LSG
     245    data N_ax/       -1.,   -1.,     8.e6,     3.e6,  -1.,   -1.,     8.e6,     3.e6,     4.e6/
     246    data N_bx/       -1.,   -1.,      0.0,      0.0,  -1.,   -1.,      0.0,      0.0,      0.0/
     247    data alpha_x/    -1.,   -1.,      0.0,      0.0,  -1.,   -1.,      0.0,      0.0,      0.0/
     248    data c_x/        -1.,   -1.,    842.0,     4.84,  -1.,   -1.,    842.0,     4.84,     94.5/
     249    data d_x/        -1.,   -1.,      0.8,     0.25,  -1.,   -1.,      0.8,     0.25,      0.5/
     250    data g_x/        -1.,   -1.,      0.5,      0.5,  -1.,   -1.,      0.5,      0.5,      0.5/
     251    data a_x/        -1.,   -1.,    524.0,    52.36,  -1.,   -1.,    524.0,    52.36,   209.44/
     252    data b_x/        -1.,   -1.,      3.0,      3.0,  -1.,   -1.,      3.0,      3.0,      3.0/
     253    data gamma_1/    -1.,   -1., 17.83725, 8.284701,  -1.,   -1., 17.83725, 8.284701, 11.63230/
     254    data gamma_2/    -1.,   -1.,      6.0,      6.0,  -1.,   -1.,      6.0,      6.0,      6.0/
     255    data gamma_3/    -1.,   -1.,      2.0,      2.0,  -1.,   -1.,      2.0,      2.0,      2.0/
     256    data gamma_4/    -1.,   -1.,      6.0,      6.0,  -1.,   -1.,      6.0,      6.0,      6.0/
     257
     258
     259
     260#endif
     261
     262
     263#ifdef MMF_V3p5_TWO_MOMENT
     264
     265    !
     266    !  Table hclass for quickbeam to support two-moment "morrison" microphysics scheme used by V3.5 (SAM 6.8)
     267    !
     268    !  This Number concentriation Np in [1/kg] MUST be input to COSP/radar simulator
     269    !
     270    !  NOTE:  Be sure to check that the ice-density (rho) set it this tables matches what you used
     271    !
     272
     273    !
     274    ! NOTE:  if ANY value in this section of code is changed, the existing LUT
     275    !        (i.e., the associated *.dat file) MUST be deleted so that a NEW
     276    !        LUT will be created !!!
     277    !
     278    character*120 :: RADAR_SIM_MICROPHYSICS_SCHEME_NAME = 'MMF_v3.5_two_moment'
     279
     280    logical :: RADAR_SIM_LOAD_scale_LUTs_flag   = .false.
     281    logical :: RADAR_SIM_UPDATE_scale_LUTs_flag = .false.
     282
     283    integer,parameter :: N_HYDRO = 9
     284
     285    integer :: HCLASS_TYPE(N_HYDRO),HCLASS_PHASE(N_HYDRO)
     286
     287    real :: HCLASS_DMIN(N_HYDRO),HCLASS_DMAX(N_HYDRO), &           
     288            HCLASS_APM(N_HYDRO),HCLASS_BPM(N_HYDRO),HCLASS_RHO(N_HYDRO), &
     289            HCLASS_P1(N_HYDRO),HCLASS_P2(N_HYDRO),HCLASS_P3(N_HYDRO)
     290
     291    ! HCLASS_CP is not used in the version of Quickbeam included in COSP
     292    !                   LSL    LSI      LSR     LSS   CVL    CVI   CVR     CVS   LSG
     293    data HCLASS_TYPE/    1,      1,      1,      1,     1,     1,    1,      1,    1/
     294    data HCLASS_PHASE/   0,      1,      0,      1,     0,     1,    0,      1,    1/
     295    data HCLASS_DMIN/   -1,     -1,     -1,     -1,    -1,    -1,   -1,     -1,   -1/
     296    data HCLASS_DMAX/   -1,     -1,     -1,     -1,    -1,    -1,   -1,     -1,   -1/
     297    data HCLASS_APM/   524,     -1,    524,     -1,   524,    -1,  524,     -1,   -1/
     298    data HCLASS_BPM/     3,     -1,      3,     -1,     3,    -1,    3,     -1,   -1/
     299    data HCLASS_RHO/    -1,    500,     -1,    100,    -1,   500,   -1,    100,  900/
     300    data HCLASS_P1/     -1,     -1,     -1,     -1,    -1,    -1,   -1,     -1,   -1/
     301    data HCLASS_P2/     -1,     -1,     -1,     -1,    -1,    -1,   -1,     -1,   -1/
     302    data HCLASS_P3/     -2,      1,      1,      1,    -2,     1,    1,      1,    1/
     303    ! Note: value of "-2" for HCLASS_P3 uses martin 1994 parameteriztion of gamma function width with Number concentration
     304#endif
     305
    131306END MODULE MOD_COSP_CONSTANTS
Note: See TracChangeset for help on using the changeset viewer.