MONC
Functions/Subroutines
sw_control_default_mod Module Reference

Functions/Subroutines

subroutine sw_control_default (sw_control)
 

Function/Subroutine Documentation

◆ sw_control_default()

subroutine sw_control_default_mod::sw_control_default ( type (strctrl), intent(inout)  sw_control)

Definition at line 20 of file sw_control_default_mod.F90.

21 
22 USE def_control, ONLY: strctrl
23 USE yomhook, ONLY: lhook, dr_hook
24 USE parkind1, ONLY: jprb, jpim
25 USE rad_pcf, ONLY: ip_solar, ip_two_stream, ip_pifm80, &
26  ip_solver_homogen_direct, ip_trunc_triangular, &
27  ip_sph_direct, ip_sph_mode_rad, ip_scatter_full, &
28  ip_max_rand, &
29  ip_homogeneous, ip_overlap_k_eqv_scl, &
30  ip_cloud_ice_water
31 
32 IMPLICIT NONE
33 
34 TYPE (StrCtrl), INTENT(INOUT) :: sw_control
35 ! The block of controlling options for the code
36 
37 INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
38 INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
39 REAL(KIND=jprb) :: zhook_handle
40 
41 
42 IF (lhook) CALL dr_hook('SW_CONTROL_DEFAULT',zhook_in,zhook_handle)
43 
44 ! Spectral region and bands
45 sw_control%isolir = ip_solar
46 sw_control%first_band = 1
47 
48 ! Physical processes
49 sw_control%l_microphysics = .true.
50 sw_control%l_gas = .true.
51 sw_control%l_rayleigh = .true.
52 sw_control%l_continuum = .true.
53 sw_control%l_cloud = .true.
54 sw_control%l_drop = .true.
55 sw_control%l_ice = .true.
56 sw_control%l_aerosol = .false.
57 sw_control%l_aerosol_ccn = .false.
58 
59 ! Properties of clouds
60 sw_control%l_local_cnv_partition = .false.
61 sw_control%l_global_cloud_top = .true.
62 
63 ! Angular integration (including algorithmic options)
64 sw_control%n_channel = 1
65 sw_control%i_angular_integration = ip_two_stream
66 sw_control%i_2stream = ip_pifm80
67 sw_control%i_solver_clear = ip_solver_homogen_direct
68 sw_control%n_order_gauss = 0
69 sw_control%i_truncation = ip_trunc_triangular
70 sw_control%i_sph_algorithm = ip_sph_direct
71 sw_control%n_order_phase_solar = 1
72 sw_control%ls_global_trunc = 9
73 sw_control%ms_min = 0
74 sw_control%ms_max = 0
75 sw_control%ls_brdf_trunc = 0
76 sw_control%accuracy_adaptive = 1.0e-04
77 sw_control%l_rescale = .true.
78 sw_control%l_henyey_greenstein_pf = .true.
79 sw_control%i_sph_mode = ip_sph_mode_rad
80 sw_control%i_solar_src = 3
81 sw_control%i_scatter_method = ip_scatter_full
82 
83 ! Switches for diagnostic output
84 sw_control%l_blue_flux_surf = .true.
85 
86 ! Satellite data
87 sw_control%sat_hgt = 0.0
88 sw_control%sat_lon = 0.0
89 sw_control%sat_lat = 0.0
90 sw_control%max_view_lon = 0.0
91 sw_control%min_view_lon = 0.0
92 sw_control%max_view_lat = 0.0
93 sw_control%min_view_lat = 0.0
94 
95 ! Originally in sw_rad_iput, defaults do not need to change for MONC
96 sw_control%i_gas_overlap = ip_overlap_k_eqv_scl
97 sw_control%l_o2 = .true.
98 sw_control%l_o3 = .true.
99 sw_control%l_h2o = .true.
100 sw_control%l_co2 = .true.
101 sw_control%l_n2o = .true.
102 sw_control%l_ch4 = .true.
103 sw_control%l_co = .false.
104 sw_control%l_nh3 = .false.
105 sw_control%l_tio = .false.
106 sw_control%l_vo = .false.
107 sw_control%l_h2 = .false.
108 sw_control%l_he = .false.
109 sw_control%l_na = .false.
110 sw_control%l_k = .false.
111 sw_control%i_st_water = 5
112 sw_control%i_cnv_water = 5
113 sw_control%i_st_ice = 8
114 sw_control%i_cnv_ice = 8
115 sw_control%i_cloud_representation = ip_cloud_ice_water
116 sw_control%i_overlap = ip_max_rand
117 sw_control%i_inhom = ip_homogeneous
118 
119 IF (lhook) CALL dr_hook('SW_CONTROL_DEFAULT',zhook_out,zhook_handle)
120 
Here is the call graph for this function:
Here is the caller graph for this function:
parkind1
Definition: parkind1.F90:7
yomhook
Definition: yomhook.F90:7
parkind1::jprb
integer, parameter jprb
Definition: parkind1.F90:24
yomhook::lhook
logical, parameter lhook
Definition: yomhook.F90:22
yomhook::dr_hook
subroutine dr_hook(name, code, handle)
Definition: yomhook.F90:27
sw_control_mod::sw_control
type(strctrl), save sw_control
Definition: sw_control_mod.F90:19
parkind1::jpim
integer, parameter jpim
Definition: parkind1.F90:23