MONC
Functions/Subroutines | Variables
sw_rad_input_mod Module Reference

Functions/Subroutines

subroutine sw_input (current_state)
 

Variables

integer(kind=jpim), parameter, private zhook_in = 0
 
integer(kind=jpim), parameter, private zhook_out = 1
 

Function/Subroutine Documentation

◆ sw_input()

subroutine sw_rad_input_mod::sw_input ( type(model_state_type), intent(inout), target  current_state)

Definition at line 38 of file sw_rad_input_mod.F90.

39 
40 USE rad_pcf, ONLY: ip_cloud_mix_max, ip_cloud_mix_random, &
41  ip_cloud_triple, ip_cloud_part_corr, ip_cloud_part_corr_cnv, &
42  ip_cloud_mcica, ip_cloud_clear, &
43  ip_solver_homogen_direct, ip_solver_mix_direct_hogan, &
44  ip_solver_triple_hogan, &
45  ip_cloud_homogen, ip_cloud_ice_water, ip_cloud_conv_strat, &
46  ip_cloud_csiw, &
47  ip_scaling, ip_mcica, &
48  ip_max_rand, ip_exponential_rand, ip_rand
49 USE ereport_mod, ONLY: ereport
50 
51 use state_mod, only : model_state_type
54 
55 IMPLICIT NONE
56 
57 type(model_state_type), target, intent(inout) :: current_state
58 INTEGER :: j, &
59  errorstatus ! Return code : 0 Normal Exit : >0 Error
60 INTEGER :: namelist_unit
61 
62 REAL(KIND=jprb) :: zhook_handle
63 
64 CHARACTER(LEN=*) :: RoutineName
65 parameter( routinename='sw_rad_input_mod')
66 CHARACTER(LEN=errormessagelength) :: CMessage ! Error message if Errorstatus >0
67 
68 IF (lhook) CALL dr_hook('SW_INPUT',zhook_in,zhook_handle)
69 
70  ! Set default values of control variables.
71 
72 CALL sw_control_default(sw_control)
73 
74 ! Transfer namelist items to the data structure.
75 sw_control%spectral_file = &
76  adjustl(options_get_string(current_state%options_database, "spectral_file_sw"))
77 sw_control%i_gas_overlap = &
78  options_get_integer(current_state%options_database, "i_gas_overlap_sw")
79 sw_control%i_st_water = &
80  options_get_integer(current_state%options_database, "i_water_sw")
81 sw_control%i_st_ice = &
82  options_get_integer(current_state%options_database, "i_ice_sw")
83 sw_control%i_cloud_representation = &
84  options_get_integer(current_state%options_database, "i_cloud_representation")
85 
86 ! Set i_cloud from combination of i_overlap and
87 
88 IF (sw_control%i_cloud_representation == ip_cloud_homogen) THEN
89 
90  sw_control%i_solver=ip_solver_homogen_direct
91  IF (sw_control%i_inhom == ip_mcica) THEN
92  ! The code below builds but if options is selected, MONC WILL NOT
93  ! run as other modules required - AH, 26/06/15
94  sw_control%i_cloud=ip_cloud_mcica
95  ELSE
96  IF (sw_control%i_overlap == ip_max_rand) THEN
97  sw_control%i_cloud=ip_cloud_mix_max
98  ELSE IF (sw_control%i_overlap == ip_exponential_rand) THEN
99  sw_control%i_cloud=ip_cloud_part_corr
100  ELSE IF (sw_control%i_overlap == ip_rand) THEN
101  sw_control%i_cloud=ip_cloud_mix_random
102  ELSE
103  errorstatus = 100
104  cmessage = 'The selected cloud overlap is not available'
105  CALL ereport(routinename, errorstatus, cmessage)
106  END IF
107  END IF
108 
109 ELSE IF (sw_control%i_cloud_representation == ip_cloud_ice_water) THEN
110 
111  IF (sw_control%i_inhom == ip_mcica) THEN
112  ! The code below builds but if options is selected, MONC WILL NOT
113  ! run as other modules required - AH, 26/06/15
114  sw_control%i_cloud=ip_cloud_mcica
115  sw_control%i_solver=ip_solver_homogen_direct
116  ELSE
117  sw_control%i_solver=ip_solver_mix_direct_hogan
118  IF (sw_control%i_overlap == ip_max_rand) THEN
119  sw_control%i_cloud=ip_cloud_mix_max
120  ELSE IF (sw_control%i_overlap == ip_exponential_rand) THEN
121  sw_control%i_cloud=ip_cloud_part_corr
122  ELSE IF (sw_control%i_overlap == ip_rand) THEN
123  sw_control%i_cloud=ip_cloud_mix_random
124  ELSE
125  errorstatus = 100
126  cmessage = 'The selected cloud overlap is not available'
127  CALL ereport(routinename, errorstatus, cmessage)
128  END IF
129  END IF
130 
131 ELSE IF ((sw_control%i_cloud_representation == ip_cloud_conv_strat) .OR. &
132  (sw_control%i_cloud_representation == ip_cloud_csiw)) THEN
133 
134  IF (sw_control%i_inhom == ip_mcica) THEN
135  errorstatus = 100
136  cmessage = 'McICA is not compatible with the selected'// &
137  ' cloud representation'
138  CALL ereport(routinename, errorstatus, cmessage)
139  ELSE
140  sw_control%i_solver=ip_solver_triple_hogan
141  IF (sw_control%i_overlap == ip_max_rand) THEN
142  sw_control%i_cloud=ip_cloud_triple
143  ELSE IF (sw_control%i_overlap == ip_exponential_rand) THEN
144  sw_control%i_cloud=ip_cloud_part_corr_cnv
145  ELSE IF (sw_control%i_overlap == ip_rand) THEN
146  sw_control%i_cloud=ip_cloud_mix_random
147  ELSE
148  errorstatus = 100
149  cmessage = 'The selected cloud overlap is not available'
150  CALL ereport(routinename, errorstatus, cmessage)
151  END IF
152  END IF
153 
154 ELSE
155 
156  ! No treatment of cloud for SW radiation
157  sw_control%l_cloud = .false.
158  sw_control%i_cloud = ip_cloud_clear
159  sw_control%i_solver = ip_solver_homogen_direct
160  sw_control%l_microphysics = .false.
161 
162 END IF
163 
164 IF (lhook) CALL dr_hook('SW_INPUT',zhook_out,zhook_handle)
165 
Here is the call graph for this function:

Variable Documentation

◆ zhook_in

integer(kind=jpim), parameter, private sw_rad_input_mod::zhook_in = 0
private

Definition at line 30 of file sw_rad_input_mod.F90.

30 INTEGER(KIND=jpim), PARAMETER, PRIVATE :: zhook_in = 0

◆ zhook_out

integer(kind=jpim), parameter, private sw_rad_input_mod::zhook_out = 1
private

Definition at line 31 of file sw_rad_input_mod.F90.

31 INTEGER(KIND=jpim), PARAMETER, PRIVATE :: zhook_out = 1
optionsdatabase_mod::options_get_integer
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
Definition: optionsdatabase.F90:217
parkind1::jprb
integer, parameter jprb
Definition: parkind1.F90:24
yomhook::lhook
logical, parameter lhook
Definition: yomhook.F90:22
optionsdatabase_mod::options_get_string
character(len=string_length) function, public options_get_string(options_database, key, index)
Retrieves a string value from the database that matches the provided key.
Definition: optionsdatabase.F90:280
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
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
optionsdatabase_mod::options_get_logical
logical function, public options_get_logical(options_database, key, index)
Retrieves a logical value from the database that matches the provided key.
Definition: optionsdatabase.F90:154
optionsdatabase_mod
Manages the options database. Contains administration functions and deduce runtime options from the c...
Definition: optionsdatabase.F90:7
optionsdatabase_mod::options_get_real
real(kind=default_precision) function, public options_get_real(options_database, key, index)
Retrieves a real value from the database that matches the provided key.
Definition: optionsdatabase.F90:91
state_mod
The model state which represents the current state of a run.
Definition: state.F90:2