source: LMDZ6/trunk/libf/phylmd/ecrad/lmdz/setup_config_from_lmdz.f90 @ 5821

Last change on this file since 5821 was 5821, checked in by idelkadi, 2 months ago

Added a formulation to prescribe effective cloud size as a hyperbolic tangent function of pressure for calculating radiative fluxes related to 3D cloud effects.
Activation is controlled in namelist_ecrad by the logical key ok_separation_tanh

File size: 5.4 KB
Line 
1module setup_config_from_lmdz
2
3  use parkind1, only : jprb
4
5  implicit none
6
7  public
8
9  type driver_config_type
10     logical    :: ok_effective_size  = .true.
11     logical    :: ok_separation_eta = .false.   
12     logical    :: ok_separation_tanh = .false.
13     real(jprb) :: high_inv_effective_size   = -1.0_jprb ! m-1
14     real(jprb) :: middle_inv_effective_size = -1.0_jprb ! m-1
15     real(jprb) :: low_inv_effective_size    = -1.0_jprb ! m-1
16     real(jprb) :: cloud_inhom_separation_factor  = -1.0_jprb
17     real(jprb) :: cloud_separation_scale_surface = -1.0_jprb
18     real(jprb) :: cloud_separation_scale_toa     = -1.0_jprb
19     real(jprb) :: cloud_separation_scale_power   = -1.0_jprb
20     real(jprb) :: frac_std = 0.75_jprb
21     real(jprb) :: overlap_decorr_length = 2000.0_jprb
22     ! KDECOLAT : 0 > cste, 1 > Shonk et al. (2010) 2 > 1 lisse a l'equateur
23     !            3 : 1+variation sur la verticale
24     !            4 : 2+variation sur la verticale
25     integer    :: kdecolat = 0
26     real(jprb) :: low_decorrelation_length = 2000.0_jprb
27     real(jprb) :: mid_decorrelation_length = 2000.0_jprb
28     real(jprb) :: high_decorrelation_length = 2000.0_jprb
29
30     ! Save inputs in "inputs.nc"
31     logical :: do_save_inputs
32 contains
33 procedure :: read => read_config_from_namelist
34
35  end type driver_config_type
36
37contains
38
39  !---------------------------------------------------------------------
40  subroutine read_config_from_namelist(this, file_name, is_success)
41
42    use radiation_io, only : nulerr, radiation_abort       
43
44    class(driver_config_type), intent(inout) :: this
45    character(*), intent(in)          :: file_name
46    logical, intent(out), optional    :: is_success
47    logical    :: ok_effective_size, ok_separation_eta, ok_separation_tanh
48    integer    :: iosopen ! Status after calling open
49    real(jprb) :: high_inv_effective_size
50    real(jprb) :: middle_inv_effective_size
51    real(jprb) :: low_inv_effective_size
52    real(jprb) :: cloud_inhom_separation_factor
53    real(jprb) :: cloud_separation_scale_surface
54    real(jprb) :: cloud_separation_scale_toa
55    real(jprb) :: cloud_separation_scale_power
56    real(jprb) :: frac_std
57    real(jprb) :: overlap_decorr_length
58    integer    :: kdecolat
59    real(jprb) :: low_decorrelation_length
60    real(jprb) :: mid_decorrelation_length
61    real(jprb) :: high_decorrelation_length
62    logical :: do_save_inputs
63
64    namelist /radiation_driver/ ok_effective_size, ok_separation_eta, ok_separation_tanh, &
65         &  frac_std, overlap_decorr_length, kdecolat, &
66         &  low_decorrelation_length, mid_decorrelation_length, high_decorrelation_length, &
67         &  high_inv_effective_size, middle_inv_effective_size, low_inv_effective_size, &
68         &  cloud_inhom_separation_factor, cloud_separation_scale_surface, &
69         &  cloud_separation_scale_toa, cloud_separation_scale_power, &
70         do_save_inputs
71
72    ok_effective_size = .false.
73    ok_separation_eta = .false.
74    ok_separation_tanh = .false.
75    high_inv_effective_size   = -1.0_jprb
76    middle_inv_effective_size = -1.0_jprb
77    low_inv_effective_size    = -1.0_jprb
78    cloud_inhom_separation_factor  = -1.0_jprb
79    cloud_separation_scale_surface = -1.0_jprb
80    cloud_separation_scale_toa     = -1.0_jprb
81    cloud_separation_scale_power   = -1.0_jprb
82    frac_std = 0.75_jprb
83    overlap_decorr_length = 2000.0_jprb
84    kdecolat = 0
85    low_decorrelation_length = 2000.0_jprb
86    mid_decorrelation_length = 2000.0_jprb
87    high_decorrelation_length = 2000.0_jprb
88    do_save_inputs = .false.
89
90    ! Open the namelist file and read the radiation_driver namelist
91    open(unit=10, iostat=iosopen, file=trim(file_name))
92    if (iosopen /= 0) then
93      ! An error occurred
94      if (present(is_success)) then
95        is_success = .false.
96        ! We now continue the subroutine so that the default values
97        ! are placed in the config structure
98      else
99        write(nulerr,'(a,a,a)') '*** Error: namelist file "', &
100             &                trim(file_name), '" not found'
101        call radiation_abort('Driver configuration error')
102      end if
103    else
104      ! Read the radiation_driver namelist, noting that it is not an
105      ! error if this namelist is not present, provided all the required
106      ! variables are present in the NetCDF data file instead
107      read(unit=10, nml=radiation_driver)
108      close(unit=10)
109    end if
110
111    ! Copy namelist data into configuration object
112    this%ok_effective_size = ok_effective_size
113    this%ok_separation_eta = ok_separation_eta
114    this%ok_separation_tanh = ok_separation_tanh
115    this%frac_std = frac_std
116    this%overlap_decorr_length = overlap_decorr_length
117    this%kdecolat = kdecolat
118    this%low_decorrelation_length = low_decorrelation_length
119    this%mid_decorrelation_length = mid_decorrelation_length
120    this%high_decorrelation_length = high_decorrelation_length
121    this%cloud_inhom_separation_factor = cloud_inhom_separation_factor
122    this%cloud_separation_scale_surface = cloud_separation_scale_surface
123    this%cloud_separation_scale_toa = cloud_separation_scale_toa
124    this%cloud_separation_scale_power = cloud_separation_scale_power
125    this%high_inv_effective_size = high_inv_effective_size
126    this%middle_inv_effective_size = middle_inv_effective_size
127    this%low_inv_effective_size = low_inv_effective_size
128    this%do_save_inputs = do_save_inputs
129
130  end subroutine read_config_from_namelist         
131
132end module setup_config_from_lmdz
Note: See TracBrowser for help on using the repository browser.