MONC
Functions/Subroutines
rad_ctl_mod Module Reference

Functions/Subroutines

subroutine rad_ctl (current_state, sw_spectrum, lw_spectrum, mcc, socrates_opt, merge_fields, socrates_derived_fields)
 

Function/Subroutine Documentation

◆ rad_ctl()

subroutine rad_ctl_mod::rad_ctl ( type(model_state_type), intent(inout), target  current_state,
type (strspecdata)  sw_spectrum,
type (strspecdata)  lw_spectrum,
type (str_mcc_profiles), intent(in)  mcc,
type (str_socrates_options), intent(in)  socrates_opt,
type (str_merge_atm), intent(inout)  merge_fields,
type (str_socrates_derived_fields), intent(inout)  socrates_derived_fields 
)

Definition at line 7 of file rad_ctl_mod.F90.

9 
10  USE def_spectrum, ONLY: strspecdata
11  USE sw_control_mod, ONLY: sw_control
12  USE lw_control_mod, ONLY: lw_control
13  USE lw_rad_input_mod, ONLY: lw_input
14  USE def_dimen, ONLY: strdim
15  USE def_atm, ONLY: stratm, deallocate_atm
16  USE def_cld, ONLY: strcld, deallocate_cld, &
17  deallocate_cld_prsc, &
18  deallocate_cld_mcica
19  USE def_aer, ONLY: straer, deallocate_aer, &
20  deallocate_aer_prsc
21  USE def_bound, ONLY: strbound, deallocate_bound
22  USE def_out, ONLY: strout, deallocate_out
23  use state_mod, only : model_state_type
24  use grids_mod, only : z_index, y_index, x_index
26  use def_merge_atm, only: str_merge_atm
29  use science_constants_mod, only: cp
30  use rad_pcf, only: ip_solar, ip_infra_red
31 
32  type(model_state_type), target, intent(inout) :: current_state
33  TYPE (StrSpecData) :: sw_spectrum
34  TYPE (StrSpecData) :: lw_spectrum
35  ! Dimensions:
36  TYPE(StrDim) :: dimen
37  ! Boundary conditions:
38  TYPE(StrBound) :: bound
39  ! atmosphere profiles
40  TYPE(StrAtm) :: atm
41  ! Cloud data:
42  TYPE(StrCld) :: cld
43  ! Aerosol data:
44  TYPE(StrAer) :: aer
45  ! radiation output
46  TYPE(StrOut) :: radout
47  ! McClatchey profile data for leves
48  type (str_mcc_profiles), intent(in) :: mcc
49  type (str_merge_atm), intent(inout) :: merge_fields
50  ! MONC options read from configuration
51  type (str_socrates_options), intent(in) :: socrates_opt
52  type (str_socrates_derived_fields), intent(inout) :: socrates_derived_fields
53 
54  integer :: icol, jcol ! Shorthand column indices from MONC (include halos)
55  integer :: target_x_index, target_y_index ! Shorthand column indices for radiation
56  !(MONC index less halos)
57  integer :: k ! index for monc k loop to work out heating rates
58  integer :: k_top ! top of the monc domain
59 
60  ! work out column indexes
61  icol=current_state%column_local_x
62  jcol=current_state%column_local_y
63  ! Use the radiation interface indexing, which does not include the halo
64  target_y_index=jcol-current_state%local_grid%halo_size(y_index)
65  target_x_index=icol-current_state%local_grid%halo_size(x_index)
66 
67  k_top = current_state%local_grid%size(z_index)
68 
69  ! ********************** Shortwave Calculation begin ***************************!
70  if (socrates_derived_fields%fraction_lit .ge. 1.0) then
71  ! SOCRATES only call for shortwave when the fraction_lit = 1
72  ! This is set in the interface (socrate_couple.F90). It is important
73  ! to note that this method and condition, does not permit a
74  ! partial lit grid
75  ! DEPENDS ON: set_control
76  call set_control(sw_control, sw_spectrum)
77  ! last argument needs to be cloud levels
78  ! DEPENDS ON: set_dimen
79  call set_dimen(sw_control, dimen, sw_spectrum, &
80  1, mcc%irad_levs, mcc%irad_levs)
81  ! DEPENDS ON: set_atm
82  ! n_profile in set_atm is the number of columns being sent to
83  ! socrates. Here it is hard-coded to 1, since socrates is called
84  ! per column in MONC
85  call set_atm(sw_control, atm, dimen, sw_spectrum, &
86  1 , mcc%irad_levs, socrates_opt, merge_fields)
87  ! DEPENDS ON: set_bound
88  call set_bound(sw_control, ip_solar, atm, dimen, sw_spectrum, bound, &
89  socrates_derived_fields)
90  ! DEPENDS ON: set_cld
91  call set_cld(sw_control, atm, dimen, sw_spectrum, cld, &
92  1 , mcc%irad_levs, mcc%irad_levs, socrates_opt, merge_fields)
93  ! DEPENDS ON: set_aer
94  call set_aer(sw_control, atm, dimen, sw_spectrum, aer )
95 
96  ! DEPENDS ON: radiance_calc
97  call radiance_calc(sw_control, dimen, sw_spectrum, atm, cld, aer, bound, radout)
98 
99  ! store the top of atmospher and surface values for diagnostics
100  socrates_derived_fields%toa_up_shortwave(target_y_index,target_x_index) = &
101  radout%flux_up(1,0,1)
102  socrates_derived_fields%toa_down_shortwave(target_y_index,target_x_index) = &
103  radout%flux_down(1,0,1)
104  socrates_derived_fields%surface_up_shortwave(target_y_index,target_x_index) = &
105  radout%flux_up(1,mcc%irad_levs,1)
106  socrates_derived_fields%surface_down_shortwave(target_y_index,target_x_index) = &
107  radout%flux_down(1,mcc%irad_levs,1)
108 
109  do k = 1, mcc%irad_levs
110  merge_fields%sw_heat_rate_radlevs(k) = &
111  ! net flux at k-1
112  ((radout%flux_down(1,k-1,1)-radout%flux_up(1,k-1,1)) &
113  ! net flux at k
114  - (radout%flux_down(1,k,1)-radout%flux_up(1,k,1)))/ &
115  (merge_fields%mass(k)*cp)
116  enddo
117 
118  do k = 1, k_top
119  socrates_derived_fields%flux_up_sw(k,target_y_index, target_x_index) = &
120  radout%flux_up(1,mcc%irad_levs+1-k,1)
121 
122  socrates_derived_fields%flux_down_sw(k,target_y_index, target_x_index) = &
123  radout%flux_down(1,mcc%irad_levs+1-k,1)
124  enddo
125 
126  current_state%sth_sw%data(1,jcol, icol) = 0.0
127  ! NB: the +2 is becasue n=1 is below the surface (comment from LEM)
128  current_state%sth_sw%data(2:k_top,jcol, icol) = &
129  merge_fields%sw_heat_rate_radlevs(mcc%irad_levs:mcc%irad_levs+2-k_top:-1)
130  socrates_derived_fields%swrad_hr(:,target_y_index, target_x_index) = &
131  current_state%sth_sw%data(:,jcol, icol)
132  ! convert dT/dt to dTH/dt
133  current_state%sth_sw%data(:, jcol, icol) = &
134  current_state%sth_sw%data(:, jcol, icol)* &
135  current_state%global_grid%configuration%vertical%prefrcp(:)
136 
137  else
138  do k = 1, k_top
139  socrates_derived_fields%flux_up_sw(k,target_y_index, target_x_index) = &
140  0.0
141 
142  socrates_derived_fields%flux_down_sw(k,target_y_index, target_x_index) = &
143  0.0
144  enddo
145  socrates_derived_fields%toa_up_shortwave(target_y_index,target_x_index) = 0.0
146  socrates_derived_fields%toa_down_shortwave(target_y_index,target_x_index) = 0.0
147  socrates_derived_fields%surface_up_shortwave(target_y_index,target_x_index) = 0.0
148  socrates_derived_fields%surface_down_shortwave(target_y_index,target_x_index) = 0.0
149  current_state%sth_sw%data(:,jcol, icol) = 0.0
150  socrates_derived_fields%swrad_hr(:,target_y_index, target_x_index) = 0.0
151 
152  endif
153 
154  CALL deallocate_out(radout)
155  CALL deallocate_aer_prsc(aer)
156  CALL deallocate_aer(aer)
157  !!$ CALL deallocate_cld_mcica(cld)
158  CALL deallocate_bound(bound)
159  CALL deallocate_cld_prsc(cld)
160  CALL deallocate_cld(cld)
161  call deallocate_atm(atm)
162  ! ********************** Shortwave Calculation end ******************************!
163 
164  ! ********************** Longwave Calculation begin *****************************!
165  ! DEPENDS ON: set_control
166  call set_control(lw_control, lw_spectrum)
167  ! DEPENDS ON: set_dimen
168  call set_dimen(lw_control, dimen, lw_spectrum, &
169  1, mcc%irad_levs, mcc%irad_levs)
170  ! DEPENDS ON: set_atm
171  call set_atm(lw_control, atm, dimen, lw_spectrum, &
172  1 , mcc%irad_levs, socrates_opt, merge_fields)
173  ! DEPENDS ON: set_bound
174  call set_bound(lw_control, ip_infra_red, atm, dimen, lw_spectrum, bound, &
175  socrates_derived_fields)
176  ! DEPENDS ON: set_cld
177  call set_cld(lw_control, atm, dimen, lw_spectrum, cld , &
178  1 , mcc%irad_levs, mcc%irad_levs, socrates_opt, merge_fields)
179  ! DEPENDS ON: set_aer
180  call set_aer(lw_control, atm, dimen, lw_spectrum, aer )
181  ! DEPENDS ON: radiance_calc
182  call radiance_calc(lw_control, dimen, lw_spectrum, atm, cld, aer, bound, radout)
183 
184  socrates_derived_fields%toa_up_longwave(target_y_index,target_x_index) = &
185  radout%flux_up(1,0,1)
186  socrates_derived_fields%surface_up_longwave(target_y_index,target_x_index) = &
187  radout%flux_up(1,mcc%irad_levs,1)
188  socrates_derived_fields%surface_down_longwave(target_y_index,target_x_index) = &
189  radout%flux_down(1,mcc%irad_levs,1)
190 
191  do k = 1, mcc%irad_levs
192  merge_fields%lw_heat_rate_radlevs(k) = &
193  ! net flux at k-1
194  ((radout%flux_down(1,k-1,1)-radout%flux_up(1,k-1,1)) &
195  ! net flux at k
196  - (radout%flux_down(1,k,1)-radout%flux_up(1,k,1)))/ &
197  (merge_fields%mass(k)*cp)
198  enddo
199 
200  current_state%sth_lw%data(1,jcol, icol) = 0.0
201  ! NB: the +2 is becasue n=1 is below the surface (comment from LEM)
202  current_state%sth_lw%data(2:k_top,jcol, icol) = &
203  merge_fields%lw_heat_rate_radlevs(mcc%irad_levs:mcc%irad_levs+2-k_top:-1)
204  ! convert dT/dt to dTH/dt
205  current_state%sth_lw%data(:, jcol, icol) = &
206  current_state%sth_lw%data(:, jcol, icol)* &
207  current_state%global_grid%configuration%vertical%prefrcp(:)
208 
209  socrates_derived_fields%lwrad_hr(:,target_y_index, target_x_index) = &
210  current_state%sth_lw%data(:,jcol, icol)
211 
212  do k = 1, k_top
213  socrates_derived_fields%flux_up_lw(k,target_y_index, target_x_index) = &
214  radout%flux_up(1,mcc%irad_levs+1-k,1)
215 
216  socrates_derived_fields%flux_down_lw(k,target_y_index, target_x_index) = &
217  radout%flux_down(1,mcc%irad_levs+1-k,1)
218  enddo
219 
220  socrates_derived_fields%totrad_hr(:,target_y_index, target_x_index) = &
221  socrates_derived_fields%lwrad_hr(:,target_y_index, target_x_index) + &
222  socrates_derived_fields%swrad_hr(:,target_y_index, target_x_index)
223 
224  CALL deallocate_out(radout)
225  CALL deallocate_aer_prsc(aer)
226  CALL deallocate_aer(aer)
227  CALL deallocate_bound(bound)
228  CALL deallocate_cld_prsc(cld)
229  CALL deallocate_cld(cld)
230  CALL deallocate_atm(atm)
231  ! ********************** Longwave Calculation end ********************************!
232 
Here is the call graph for this function:
lw_control_mod
Definition: lw_control_mod.F90:13
def_mcc_profiles
Definition: def_mcc_profiles.F90:1
def_mcc_profiles::str_mcc_profiles
Definition: def_mcc_profiles.F90:7
def_socrates_derived_fields
Definition: def_socrates_derived_fields.F90:1
grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
sw_control_mod
Definition: sw_control_mod.F90:13
science_constants_mod::cp
real(kind=default_precision), public cp
Definition: scienceconstants.F90:13
set_atm
subroutine set_atm(control, atm, dimen, spectrum, n_profile, n_layer, socrates_opt, merge_fields)
Definition: set_atm.F90:19
lw_control_mod::lw_control
type(strctrl), save lw_control
Definition: lw_control_mod.F90:19
set_cld
subroutine set_cld(control, atm, dimen, spectrum, cld, n_profile, n_layer, nclds, socrates_opt, merge_fields)
Definition: set_cld.F90:18
set_bound
subroutine set_bound(control, isolir, atm, dimen, spectrum, bound, socrates_derived_fields)
Definition: set_bound.F90:14
set_control
subroutine set_control(control, spectrum)
Definition: set_control.F90:15
def_merge_atm::str_merge_atm
Definition: def_merge_atm.F90:10
science_constants_mod
Scientific constant values used throughout simulations. Each has a default value and this can be over...
Definition: scienceconstants.F90:3
lw_rad_input_mod
Definition: lw_rad_input_mod.F90:18
def_socrates_options::str_socrates_options
Definition: def_socrates_options.F90:7
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
sw_control_mod::sw_control
type(strctrl), save sw_control
Definition: sw_control_mod.F90:19
lw_rad_input_mod::lw_input
subroutine lw_input(current_state, lw_control)
Definition: lw_rad_input_mod.F90:39
set_dimen
subroutine set_dimen(control, dimen, spectrum, n_points, model_levels, cloud_levels)
Definition: set_dimen.F90:16
set_aer
subroutine set_aer(control, atm, dimen, spectrum, aer)
Definition: set_aer.F90:14
def_socrates_derived_fields::str_socrates_derived_fields
Definition: def_socrates_derived_fields.F90:7
def_socrates_options
Definition: def_socrates_options.F90:1
def_merge_atm
Definition: def_merge_atm.F90:1
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
state_mod
The model state which represents the current state of a run.
Definition: state.F90:2