source: LMDZ6/trunk/libf/phylmd/ecrad/driver/ecrad_driver_config.F90 @ 4773

Last change on this file since 4773 was 4773, checked in by idelkadi, 6 months ago
  • Update of Ecrad in LMDZ The same organization of the Ecrad offline version is retained in order to facilitate the updating of Ecrad in LMDZ and the comparison between online and offline results. version 1.6.1 of Ecrad (https://github.com/lguez/ecrad.git)
  • Implementation of the double call of Ecrad in LMDZ


File size: 15.9 KB
Line 
1! ecrad_driver_config.F90 - Configure driver for offline ecRad radiation scheme
2!
3! (C) Copyright 2015- ECMWF.
4!
5! This software is licensed under the terms of the Apache Licence Version 2.0
6! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
7!
8! In applying this licence, ECMWF does not waive the privileges and immunities
9! granted to it by virtue of its status as an intergovernmental organisation
10! nor does it submit to any jurisdiction.
11!
12! Author:  Robin Hogan
13! Email:   r.j.hogan@ecmwf.int
14
15module ecrad_driver_config
16
17  use parkind1,                      only : jprb
18
19  implicit none
20
21  public
22
23  ! Max length of "experiment" global attribute
24  integer, parameter :: NMaxStringLength = 2000
25
26  ! Maximum number of spectral diagnostics
27  integer, parameter :: NMaxSpectralDiag = 256
28 
29  type driver_config_type
30
31     ! Parallel settings
32     logical :: do_parallel
33     integer :: nblocksize ! Number of columns processed at once
34
35     ! Override values from the radiation_override namelist (mostly
36     ! related to clouds): these will override any values in the
37     ! NetCDF data file (or scale them)
38     real(jprb) :: fractional_std_override
39     real(jprb) :: overlap_decorr_length_override
40     real(jprb) :: high_inv_effective_size_override   = -1.0_jprb ! m-1
41     real(jprb) :: middle_inv_effective_size_override = -1.0_jprb ! m-1
42     real(jprb) :: low_inv_effective_size_override    = -1.0_jprb ! m-1
43     real(jprb) :: effective_size_scaling
44     real(jprb) :: sw_albedo_override
45     real(jprb) :: lw_emissivity_override
46     real(jprb) :: q_liq_scaling, q_ice_scaling
47     real(jprb) :: cloud_fraction_scaling
48     real(jprb) :: overlap_decorr_length_scaling
49     real(jprb) :: skin_temperature_override ! K
50     real(jprb) :: solar_irradiance_override ! W m-2
51     real(jprb) :: solar_cycle_multiplier_override
52     real(jprb) :: cos_sza_override
53     real(jprb) :: cloud_inhom_separation_factor  = 1.0_jprb
54     real(jprb) :: cloud_separation_scale_surface = -1.0_jprb
55     real(jprb) :: cloud_separation_scale_toa     = -1.0_jprb
56     real(jprb) :: cloud_separation_scale_power   = 1.0_jprb
57     real(jprb) :: h2o_scaling    = 1.0_jprb
58     real(jprb) :: co2_scaling    = 1.0_jprb
59     real(jprb) :: o3_scaling     = 1.0_jprb
60     real(jprb) :: co_scaling     = 1.0_jprb
61     real(jprb) :: ch4_scaling    = 1.0_jprb
62     real(jprb) :: n2o_scaling    = 1.0_jprb
63     real(jprb) :: o2_scaling     = 1.0_jprb
64     real(jprb) :: cfc11_scaling  = 1.0_jprb
65     real(jprb) :: cfc12_scaling  = 1.0_jprb
66     real(jprb) :: hcfc22_scaling = 1.0_jprb
67     real(jprb) :: ccl4_scaling   = 1.0_jprb
68     real(jprb) :: no2_scaling    = 1.0_jprb
69
70     ! Optional monotonically increasing wavelength bounds (m) for
71     ! shortwave spectral flux diagnostics, to be written to
72     ! sw_diagnostic_file_name
73     real(jprb) :: sw_diag_wavelength_bound(NMaxSpectralDiag+1) = -1.0_jprb
74
75     ! Name of file to write shortwave spectral diagnostics to, but
76     ! only if sw_diag_wavelength_bound is populated via the namelist
77     character(len=NMaxStringLength) :: sw_diag_file_name = 'sw_diagnostics.nc'
78
79     ! Number of shortwave diagnostics, worked out from first
80     ! unassigned value in sw_diag_wavelength_bound after reading
81     ! namelist
82     integer :: n_sw_diag
83     
84     ! Volume mixing ratios (m3 m-3) in model layers (or equivalently
85     ! mole fractions (mol mol-1)) are typically stored in the input
86     ! file with a name like co2_vmr, but the suffix can be overridden
87     ! by the user
88     character(len=32) :: vmr_suffix_str = '_vmr'
89
90     ! Process a limited number of columns (iendcol=0 indicates to
91     ! process from istartcol up to the end)
92     integer :: istartcol, iendcol
93
94     ! Save inputs in "inputs.nc"
95     logical :: do_save_inputs
96     
97     ! Save aerosol optical properties to "aerosol_optics.nc"
98     logical :: do_save_aerosol_optics
99
100     ! Save aerosol optical properties to "hydrometeor_optics*.nc"
101     logical :: do_save_cloud_optics
102
103     ! Save only net and surface/TOA fluxes, rather than up and down
104     logical :: do_save_net_fluxes
105     
106     ! Do we ignore the inv_inhom_effective_size variable and instead
107     ! assume the scale of cloud inhomogeneities is the same as the
108     ! scale of the clouds themselves?
109     logical :: do_ignore_inhom_effective_size = .false.
110
111     ! Number of repeats (for benchmarking)
112     integer :: nrepeat
113
114     ! Do we correct unphysical inputs (e.g. negative gas concentrations)?
115     logical :: do_correct_unphysical_inputs = .false.
116
117     ! Do we write NetCDF4/HDF5 file format, needed for very large
118     ! files?
119     logical :: do_write_hdf5 = .false.
120
121     ! Do we write fluxes in double precision?
122     logical :: do_write_double_precision = .false.
123
124     ! Name of the experiment, to save in output file
125     character(len=NMaxStringLength) :: experiment_name = ''
126
127     ! Control verbosity in driver routine: 0=none (no output to
128     ! standard output; write to standard error only if an error
129     ! occurs), 1=warning, 2=info, 3=progress, 4=detailed, 5=debug
130     integer :: iverbose
131
132   contains
133     procedure :: read => read_config_from_namelist
134
135  end type driver_config_type
136
137contains
138
139  !---------------------------------------------------------------------
140  ! This subroutine reads configuration data from a namelist file, and
141  ! anything that is not in the namelists will be set to default
142  ! values. If optional output argument "is_success" is present, then on
143  ! error (e.g. missing file) it will be set to .false.; if this
144  ! argument is missing then on error the program will be aborted.
145  subroutine read_config_from_namelist(this, file_name, is_success)
146
147    use radiation_io, only : nulerr, radiation_abort
148
149    class(driver_config_type), intent(inout) :: this
150    character(*), intent(in)          :: file_name
151    logical, intent(out), optional    :: is_success
152
153    integer :: iosopen ! Status after calling open
154
155    ! Override and scaling values
156    real(jprb) :: fractional_std
157    real(jprb) :: overlap_decorr_length
158    real(jprb) :: inv_effective_size
159    real(jprb) :: high_inv_effective_size
160    real(jprb) :: middle_inv_effective_size
161    real(jprb) :: low_inv_effective_size
162    real(jprb) :: effective_size_scaling
163    real(jprb) :: sw_albedo
164    real(jprb) :: lw_emissivity
165    real(jprb) :: q_liquid_scaling, q_ice_scaling
166    real(jprb) :: cloud_fraction_scaling
167    real(jprb) :: overlap_decorr_length_scaling
168    real(jprb) :: skin_temperature
169    real(jprb) :: cos_solar_zenith_angle
170    real(jprb) :: solar_irradiance_override
171    real(jprb) :: solar_cycle_multiplier_override
172    real(jprb) :: cloud_inhom_separation_factor
173    real(jprb) :: cloud_separation_scale_surface
174    real(jprb) :: cloud_separation_scale_toa
175    real(jprb) :: cloud_separation_scale_power
176    real(jprb) :: h2o_scaling   
177    real(jprb) :: co2_scaling   
178    real(jprb) :: o3_scaling   
179    real(jprb) :: co_scaling   
180    real(jprb) :: ch4_scaling   
181    real(jprb) :: n2o_scaling
182    real(jprb) :: o2_scaling   
183    real(jprb) :: cfc11_scaling
184    real(jprb) :: cfc12_scaling
185    real(jprb) :: hcfc22_scaling
186    real(jprb) :: ccl4_scaling 
187    real(jprb) :: no2_scaling   
188    real(jprb) :: sw_diag_wavelength_bound(NMaxSpectralDiag+1)
189    character(len=NMaxStringLength) :: sw_diag_file_name
190    character(len=32) :: vmr_suffix_str
191    character(len=NMaxStringLength) :: experiment_name
192
193    ! Parallel settings
194    logical :: do_parallel
195    integer :: nblocksize
196
197    logical :: do_save_inputs, do_save_aerosol_optics, do_save_net_fluxes, &
198         &  do_save_cloud_optics, do_ignore_inhom_effective_size, &
199         &  do_correct_unphysical_inputs, do_write_hdf5, &
200         &  do_write_double_precision
201    integer :: nrepeat
202
203    ! Process a limited number of columns (iendcol=0 indicates to
204    ! process from istartcol up to the end)
205    integer :: istartcol, iendcol
206
207    ! Verbosity
208    integer :: iverbose
209
210    ! Are we going to override the effective size?
211    logical :: do_override_eff_size
212
213    ! Loop index
214    integer :: jdiag
215   
216    namelist /radiation_driver/ fractional_std, &
217         &  overlap_decorr_length, inv_effective_size, sw_albedo, &
218         &  high_inv_effective_size, middle_inv_effective_size, &
219         &  low_inv_effective_size, cloud_inhom_separation_factor, &
220         &  effective_size_scaling, cos_solar_zenith_angle, &
221         &  lw_emissivity, q_liquid_scaling, q_ice_scaling, &
222         &  istartcol, iendcol, solar_irradiance_override, &
223         &  solar_cycle_multiplier_override, &
224         &  cloud_fraction_scaling, overlap_decorr_length_scaling, &
225         &  skin_temperature, do_parallel, nblocksize, iverbose, &
226         &  nrepeat, do_save_inputs, do_ignore_inhom_effective_size, &
227         &  do_save_aerosol_optics, do_save_net_fluxes, do_save_cloud_optics, &
228         &  cloud_separation_scale_toa, cloud_separation_scale_surface, &
229         &  cloud_separation_scale_power, do_correct_unphysical_inputs, &
230         &  do_write_hdf5, h2o_scaling, co2_scaling, o3_scaling, co_scaling, &
231         &  ch4_scaling, o2_scaling, cfc11_scaling, cfc12_scaling, &
232         &  hcfc22_scaling, no2_scaling, n2o_scaling, ccl4_scaling, &
233         &  vmr_suffix_str, experiment_name, do_write_double_precision, &
234         &  sw_diag_wavelength_bound, sw_diag_file_name
235
236    ! Default values
237    do_parallel = .true.
238    do_save_inputs = .false.
239    do_save_aerosol_optics = .false.
240    do_save_cloud_optics = .false.
241    do_save_net_fluxes = .false.
242    do_ignore_inhom_effective_size = .false.
243    nblocksize = 8
244
245    ! Negative values indicate no override will take place
246    fractional_std = -1.0_jprb
247    overlap_decorr_length = -1.0_jprb
248    inv_effective_size = -1.0_jprb
249    high_inv_effective_size = -1.0_jprb
250    middle_inv_effective_size = -1.0_jprb
251    low_inv_effective_size = -1.0_jprb
252    effective_size_scaling = -1.0_jprb
253    sw_albedo = -1.0_jprb
254    lw_emissivity = -1.0_jprb
255    q_liquid_scaling = -1.0_jprb
256    q_ice_scaling = -1.0_jprb
257    cloud_fraction_scaling = -1.0_jprb
258    overlap_decorr_length_scaling = -1.0_jprb
259    skin_temperature = -1.0_jprb
260    cos_solar_zenith_angle = -1.0_jprb
261    solar_irradiance_override = -1.0_jprb
262    solar_cycle_multiplier_override = -2.0e6_jprb
263    cloud_inhom_separation_factor = 1.0_jprb
264    cloud_separation_scale_toa = -1.0_jprb
265    cloud_separation_scale_surface = -1.0_jprb
266    cloud_separation_scale_power = 1.0_jprb
267    h2o_scaling    = 1.0_jprb
268    co2_scaling    = 1.0_jprb
269    o3_scaling     = 1.0_jprb
270    co_scaling     = 1.0_jprb
271    ch4_scaling    = 1.0_jprb
272    n2o_scaling    = 1.0_jprb
273    o2_scaling     = 1.0_jprb
274    cfc11_scaling  = 1.0_jprb
275    cfc12_scaling  = 1.0_jprb
276    hcfc22_scaling = 1.0_jprb
277    ccl4_scaling   = 1.0_jprb
278    no2_scaling    = 1.0_jprb
279    vmr_suffix_str = '_vmr';
280    iverbose = 2 ! Default verbosity is "warning"
281    istartcol = 0
282    iendcol = 0
283    nrepeat = 1
284    do_correct_unphysical_inputs = .false.
285    do_write_hdf5 = .false.
286    do_write_double_precision = .false.
287    experiment_name = ''
288    sw_diag_wavelength_bound = this%sw_diag_wavelength_bound
289    sw_diag_file_name = this%sw_diag_file_name
290   
291    ! Open the namelist file and read the radiation_driver namelist
292    open(unit=10, iostat=iosopen, file=trim(file_name))
293    if (iosopen /= 0) then
294      ! An error occurred
295      if (present(is_success)) then
296        is_success = .false.
297        ! We now continue the subroutine so that the default values
298        ! are placed in the config structure
299      else
300        write(nulerr,'(a,a,a)') '*** Error: namelist file "', &
301             &                trim(file_name), '" not found'
302        call radiation_abort('Driver configuration error')
303      end if
304    else
305      ! Read the radiation_driver namelist, noting that it is not an
306      ! error if this namelist is not present, provided all the required
307      ! variables are present in the NetCDF data file instead
308      read(unit=10, nml=radiation_driver)
309      close(unit=10)
310    end if
311
312    ! Copy namelist data into configuration object
313    this%do_parallel = do_parallel
314    this%do_save_inputs = do_save_inputs
315    this%do_save_aerosol_optics = do_save_aerosol_optics
316    this%do_save_cloud_optics = do_save_cloud_optics
317    this%do_save_net_fluxes = do_save_net_fluxes
318    this%do_ignore_inhom_effective_size = do_ignore_inhom_effective_size
319    this%nblocksize = nblocksize
320    this%iverbose = iverbose
321    this%nrepeat = nrepeat
322    if (istartcol < 1) then
323      this%istartcol = 1
324    else
325      this%istartcol = istartcol
326    end if
327    if (iendcol < 1) then
328      this%iendcol = 0
329    else
330      this%iendcol = iendcol
331    end if
332
333    ! Set override values
334    this%fractional_std_override = fractional_std
335    this%overlap_decorr_length_override = overlap_decorr_length
336
337    do_override_eff_size = .false.
338    if (inv_effective_size >= 0.0_jprb) then
339      this%high_inv_effective_size_override = inv_effective_size
340      this%middle_inv_effective_size_override = inv_effective_size
341      this%low_inv_effective_size_override = inv_effective_size
342    end if
343    if (high_inv_effective_size >= 0.0_jprb) then
344      this%high_inv_effective_size_override = high_inv_effective_size
345      do_override_eff_size = .true.
346    end if
347    if (middle_inv_effective_size >= 0.0_jprb) then
348      this%middle_inv_effective_size_override = middle_inv_effective_size
349      do_override_eff_size = .true.
350    end if
351    if (low_inv_effective_size >= 0.0_jprb) then
352      this%low_inv_effective_size_override = low_inv_effective_size
353      do_override_eff_size = .true.
354    end if
355
356    if (do_override_eff_size &
357         &  .and. (this%high_inv_effective_size_override < 0.0_jprb &
358              .or. this%middle_inv_effective_size_override < 0.0_jprb &
359              .or. this%low_inv_effective_size_override < 0.0_jprb)) then
360      write(nulerr,'(a)') '*** Error: inverse effective cloud size not specified for high, middle and low clouds"'
361      call radiation_abort('Driver configuration error')
362    end if
363
364    this%effective_size_scaling = effective_size_scaling
365    this%sw_albedo_override = sw_albedo
366    this%lw_emissivity_override = lw_emissivity
367    this%q_liq_scaling = q_liquid_scaling
368    this%q_ice_scaling = q_ice_scaling
369    this%cloud_fraction_scaling = cloud_fraction_scaling
370    this%overlap_decorr_length_scaling = overlap_decorr_length_scaling
371    this%skin_temperature_override = skin_temperature
372    this%cos_sza_override = cos_solar_zenith_angle
373    this%solar_irradiance_override = solar_irradiance_override
374    this%solar_cycle_multiplier_override = solar_cycle_multiplier_override
375    this%cloud_inhom_separation_factor = cloud_inhom_separation_factor
376    this%cloud_separation_scale_toa = cloud_separation_scale_toa
377    this%cloud_separation_scale_surface = cloud_separation_scale_surface
378    this%cloud_separation_scale_power = cloud_separation_scale_power
379    this%do_correct_unphysical_inputs = do_correct_unphysical_inputs
380    this%do_write_hdf5  = do_write_hdf5
381    this%do_write_double_precision = do_write_double_precision
382    this%h2o_scaling    = h2o_scaling
383    this%co2_scaling    = co2_scaling
384    this%o3_scaling     = o3_scaling
385    this%co_scaling     = co_scaling
386    this%ch4_scaling    = ch4_scaling
387    this%n2o_scaling    = n2o_scaling
388    this%o2_scaling     = o2_scaling
389    this%cfc11_scaling  = cfc11_scaling
390    this%cfc12_scaling  = cfc12_scaling
391    this%hcfc22_scaling = hcfc22_scaling
392    this%ccl4_scaling   = ccl4_scaling
393    this%no2_scaling    = no2_scaling
394    this%vmr_suffix_str = trim(vmr_suffix_str)
395    this%experiment_name= trim(experiment_name)
396   
397    this%sw_diag_file_name = trim(sw_diag_file_name)
398    this%sw_diag_wavelength_bound = sw_diag_wavelength_bound
399    ! Work out number of shortwave diagnostics from first negative
400    ! wavelength bound, noting that the number of diagnostics is one
401    ! fewer than the number of valid bounds
402    do jdiag = 0,NMaxSpectralDiag
403      if (this%sw_diag_wavelength_bound(jdiag+1) < 0.0_jprb) then
404        this%n_sw_diag = max(0,jdiag-1)
405        exit
406      end if
407    end do
408   
409  end subroutine read_config_from_namelist
410
411end module ecrad_driver_config
Note: See TracBrowser for help on using the repository browser.