MONC
Functions/Subroutines
set_control.F90 File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine set_control (control, spectrum)
 

Function/Subroutine Documentation

◆ set_control()

subroutine set_control ( type(strctrl), intent(inout)  control,
type (strspecdata), intent(in)  spectrum 
)

Definition at line 14 of file set_control.F90.

15 
16 
17 USE rad_pcf
18 USE def_control, ONLY: strctrl, allocate_control
19 USE def_spectrum, ONLY: strspecdata
20 USE ereport_mod, ONLY: ereport
21 USE errormessagelength_mod, ONLY: errormessagelength
22 
23 IMPLICIT NONE
24 
25 
26 ! Control options:
27 TYPE(StrCtrl), INTENT(INOUT) :: control
28 
29 ! Spectral data:
30 TYPE (StrSpecData), INTENT(IN) :: spectrum
31 
32 ! Local variables.
33 INTEGER :: i
34 ! Loop variable
35 
36 INTEGER :: ierr = i_normal
37 CHARACTER (LEN=*), PARAMETER :: RoutineName = 'set_control'
38 CHARACTER (LEN=errormessagelength) :: cmessage
39 
40 
41 ! By default in MONC we assume mixing ratios so set following
42 ! to true
43 LOGICAL :: l_mixing_ratio = .true.
44 ! True if mixing ratios are with respect to dry mass
45 
46 ! Set the last band to use as the last band in the spectral file
47  control%last_band = spectrum%basic%n_band
48 
49 ! Allocate band-by-band control options
50  CALL allocate_control(control, spectrum)
51 
52 ! Set diagnostic flags
53 SELECT CASE (control%isolir)
54 
55 CASE (ip_solar)
56  control%l_clear = .true.
57  control%l_cloud_extinction = .true.
58  control%l_ls_cloud_extinction = .true.
59  control%l_cnv_cloud_extinction = .false.
60 
61 CASE (ip_infra_red)
62  control%l_clear = .true.
63  control%l_cloud_absorptivity = .true.
64  control%l_ls_cloud_absorptivity = .true.
65  control%l_cnv_cloud_absorptivity = .false.
66 
67 END SELECT
68 
69 ! Control flag for corrections to the direct solar flux at the surface
70 ! for sloping terrain
71 control%l_orog = .false.
72 
73 ! Decide on the final options for aerosols:
74 control%l_aerosol_mode = .false.
75 control%l_aerosol = .false.
76 control%l_aerosol_ccn=.false.
77 
78 
79 ! Set properties for individual bands.
80 DO i = 1, spectrum%basic%n_band
81  control%map_channel(i) = 1
82  control%weight_band(i) = 1.0
83  control%i_scatter_method_band(i) = control%i_scatter_method
84  control%i_gas_overlap_band(i) = control%i_gas_overlap
85  IF (any(spectrum%gas%i_scale_fnc(i,:) == ip_scale_ses2)) THEN
86  ! If SES2 scaling is used in this band then the overlap must also use SES2:
87  control%i_gas_overlap_band(i) = ip_overlap_mix_ses2
88  END IF
89 END DO
90 
91 
92 IF (control%i_angular_integration == ip_two_stream) THEN
93 
94  IF (control%l_rescale) control%n_order_forward=2
95  control%l_tile=.false.
96 
97 ELSE IF (control%i_angular_integration == ip_spherical_harmonic) THEN
98 
99  IF (control%i_sph_mode == ip_sph_mode_flux) THEN
100  ! Map all bands to a single output channel
101  control%n_channel = 1
102  control%map_channel(1:spectrum%basic%n_band) = 1
103  ELSE
104  ! Map each band to a separate output channel
105  control%n_channel = spectrum%basic%n_band
106  DO i = 1, spectrum%basic%n_band
107  control%map_channel(i) = i
108  END DO
109  END IF
110 
111  IF (control%l_rescale) control%n_order_forward=control%ls_global_trunc+1
112 
113  ! As currently implemented, Euler's transformation is applied
114  ! only in its most basic form, adding just half of the last
115  ! term in an alternating series.
116  IF (control%l_euler_trnf) THEN
117  control%euler_factor=0.5
118  ELSE
119  control%euler_factor=1.0
120  END IF
121 
122  ! Clear-sky fluxes are not available from the spherical harmonic
123  ! code in the same call as cloudy fluxes yet. If required, they
124  ! should be diagnosed by using a separate call to the code with
125  ! clouds switched off.
126  IF ( control%l_clear ) THEN
127  cmessage = 'Clear-sky fluxes not directly available in harmonics'
128  ierr=i_err_fatal
129  GO TO 9999
130  END IF
131 
132  ! We permit tiling of sea-ice points only with the two-stream
133  ! option at present.
134  control%l_tile=.false.
135 
136 END IF
137 
138 
139 9999 CONTINUE
140 ! Check error condition
141 IF (ierr /= i_normal) THEN
142  CALL ereport(routinename, ierr, cmessage)
143 END IF
144 
Here is the caller graph for this function: