MONC
Functions/Subroutines | Variables
simplecloud_mod Module Reference

A very simple saturation adjustment scheme without any microphysics. More...

Functions/Subroutines

type(component_descriptor_type) function, public simplecloud_get_descriptor ()
 Provides the descriptor back to the caller and is used in component registration. More...
 
subroutine field_information_retrieval_callback (current_state, name, field_information)
 Field information retrieval callback, this returns information for a specific components published field. More...
 
subroutine field_value_retrieval_callback (current_state, name, field_value)
 The initialisation callback sets up the moisture fields. More...
 
subroutine initialisation_callback (current_state)
 
subroutine finalisation_callback (current_state)
 
subroutine timestep_callback (current_state)
 Called for each column per timestep this will apply a forcing term to the aerosol fields. More...
 
subroutine save_precomponent_tendencies (current_state, cxn, cyn, txn, tyn)
 Save the 3d tendencies coming into the component. More...
 
subroutine compute_component_tendencies (current_state, cxn, cyn, txn, tyn)
 Computation of component tendencies. More...
 
subroutine set_published_field_value (field_value, real_1d_field, real_2d_field, real_3d_field)
 Sets the published field value from the temporary diagnostic values held by this component. More...
 

Variables

integer iqv
 
integer iql
 
integer k_cloudmax
 
real(kind=default_precision) max_height_cloud
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_th
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_qv
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_ql
 
real(kind=default_precision), dimension(:,:,:), allocatable tend_3d_tabs
 
logical l_tend_3d_th
 
logical l_tend_3d_qv
 
logical l_tend_3d_ql
 
logical l_tend_3d_tabs
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_th
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_qv
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_ql
 
real(kind=default_precision), dimension(:), allocatable tend_pr_tot_tabs
 
logical l_tend_pr_tot_th
 
logical l_tend_pr_tot_qv
 
logical l_tend_pr_tot_ql
 
logical l_tend_pr_tot_tabs
 
integer diagnostic_generation_frequency
 

Detailed Description

A very simple saturation adjustment scheme without any microphysics.

Function/Subroutine Documentation

◆ compute_component_tendencies()

subroutine simplecloud_mod::compute_component_tendencies ( type(model_state_type), intent(inout), target  current_state,
integer, intent(in)  cxn,
integer, intent(in)  cyn,
integer, intent(in)  txn,
integer, intent(in)  tyn 
)
private

Computation of component tendencies.

Parameters
current_stateCurrent model state
cxnThe current slice, x, index
cynThe current column, y, index.
txntarget_x_index
tyntarget_y_index

Definition at line 421 of file simplecloud.F90.

422  type(model_state_type), target, intent(inout) :: current_state
423  integer, intent(in) :: cxn, cyn, txn, tyn
424 
425  ! Calculate change in tendency due to component
426  if (l_tend_3d_th) then
427  tend_3d_th(:,tyn,txn)=current_state%sth%data(:,cyn,cxn) - tend_3d_th(:,tyn,txn)
428  endif
429  if (l_tend_3d_qv) then
430  tend_3d_qv(:,tyn,txn)=current_state%sq(iqv)%data(:,cyn,cxn) - tend_3d_qv(:,tyn,txn)
431  endif
432  if (l_tend_3d_ql) then
433  tend_3d_ql(:,tyn,txn)=current_state%sq(iql)%data(:,cyn,cxn) - tend_3d_ql(:,tyn,txn)
434  endif
435  if (l_tend_3d_tabs) then
436  tend_3d_tabs(:,tyn,txn)= &
437  current_state%sth%data(:,cyn,cxn) * current_state%global_grid%configuration%vertical%rprefrcp(:) &
438  - tend_3d_tabs(:,tyn,txn)
439  endif
440 
441  ! Add local tendency fields to the profile total
442  if (l_tend_pr_tot_th) then
443  tend_pr_tot_th(:)=tend_pr_tot_th(:) + tend_3d_th(:,tyn,txn)
444  endif
445  if (l_tend_pr_tot_qv) then
446  tend_pr_tot_qv(:)=tend_pr_tot_qv(:) + tend_3d_qv(:,tyn,txn)
447  endif
448  if (l_tend_pr_tot_ql) then
449  tend_pr_tot_ql(:)=tend_pr_tot_ql(:) + tend_3d_ql(:,tyn,txn)
450  endif
451  if (l_tend_pr_tot_tabs) then
452  tend_pr_tot_tabs(:)=tend_pr_tot_tabs(:) + tend_3d_tabs(:,tyn,txn)
453  endif
454 
Here is the caller graph for this function:

◆ field_information_retrieval_callback()

subroutine simplecloud_mod::field_information_retrieval_callback ( type(model_state_type), intent(inout), target  current_state,
character(len=*), intent(in)  name,
type(component_field_information_type), intent(out)  field_information 
)
private

Field information retrieval callback, this returns information for a specific components published field.

Parameters
current_stateCurrent model state
nameThe name of the field to retrieve information for
field_informationPopulated with information about the field

Definition at line 74 of file simplecloud.F90.

75  type(model_state_type), target, intent(inout) :: current_state
76  character(len=*), intent(in) :: name
77  type(component_field_information_type), intent(out) :: field_information
78  integer :: strcomp
79 
80  ! Field information for 3d
81  strcomp=index(name, "simplecloud_3d_local")
82  if (strcomp .ne. 0) then
83  field_information%field_type=component_array_field_type
84  field_information%number_dimensions=3
85  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
86  field_information%dimension_sizes(2)=current_state%local_grid%size(y_index)
87  field_information%dimension_sizes(3)=current_state%local_grid%size(x_index)
88  field_information%data_type=component_double_data_type
89 
90  if (name .eq. "tend_th_simplecloud_3d_local") then
91  field_information%enabled=l_tend_3d_th
92  else if (name .eq. "tend_qv_simplecloud_3d_local") then
93  field_information%enabled=l_tend_3d_qv
94  else if (name .eq. "tend_ql_simplecloud_3d_local") then
95  field_information%enabled=l_tend_3d_ql
96  else if (name .eq. "tend_tabs_simplecloud_3d_local") then
97  field_information%enabled=l_tend_3d_tabs
98  else
99  field_information%enabled=.true.
100  end if
101 
102  end if !end 3d check
103 
104  ! Field information for profiles
105  strcomp=index(name, "simplecloud_profile_total_local")
106  if (strcomp .ne. 0) then
107  field_information%field_type=component_array_field_type
108  field_information%number_dimensions=1
109  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
110  field_information%data_type=component_double_data_type
111 
112  if (name .eq. "tend_th_simplecloud_profile_total_local") then
113  field_information%enabled=l_tend_pr_tot_th
114  else if (name .eq. "tend_qv_simplecloud_profile_total_local") then
115  field_information%enabled=l_tend_pr_tot_qv
116  else if (name .eq. "tend_ql_simplecloud_profile_total_local") then
117  field_information%enabled=l_tend_pr_tot_ql
118  else if (name .eq. "tend_tabs_simplecloud_profile_total_local") then
119  field_information%enabled=l_tend_pr_tot_tabs
120  else
121  field_information%enabled=.true.
122  end if
123 
124  end if !end profile check
125 
Here is the caller graph for this function:

◆ field_value_retrieval_callback()

subroutine simplecloud_mod::field_value_retrieval_callback ( type(model_state_type), intent(inout), target  current_state,
character(len=*), intent(in)  name,
type(component_field_value_type), intent(out)  field_value 
)
private

The initialisation callback sets up the moisture fields.

Parameters
current_stateThe current model state Field value retrieval callback, this returns the value of a specific published field
current_stateCurrent model state
nameThe name of the field to retrieve the value for
field_valuePopulated with the value of the field

Definition at line 135 of file simplecloud.F90.

136  type(model_state_type), target, intent(inout) :: current_state
137  character(len=*), intent(in) :: name
138  type(component_field_value_type), intent(out) :: field_value
139 
140  ! 3d Tendency Fields
141  if (name .eq. "tend_th_simplecloud_3d_local" .and. allocated(tend_3d_th)) then
142  call set_published_field_value(field_value, real_3d_field=tend_3d_th)
143  else if (name .eq. "tend_qv_simplecloud_3d_local" .and. allocated(tend_3d_qv)) then
144  call set_published_field_value(field_value, real_3d_field=tend_3d_qv)
145  else if (name .eq. "tend_ql_simplecloud_3d_local" .and. allocated(tend_3d_ql)) then
146  call set_published_field_value(field_value, real_3d_field=tend_3d_ql)
147  else if (name .eq. "tend_tabs_simplecloud_3d_local" .and. allocated(tend_3d_tabs)) then
148  call set_published_field_value(field_value, real_3d_field=tend_3d_tabs)
149 
150  ! Profile Tendency Fields
151  else if (name .eq. "tend_th_simplecloud_profile_total_local" .and. allocated(tend_pr_tot_th)) then
152  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_th)
153  else if (name .eq. "tend_qv_simplecloud_profile_total_local" .and. allocated(tend_pr_tot_qv)) then
154  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_qv)
155  else if (name .eq. "tend_ql_simplecloud_profile_total_local" .and. allocated(tend_pr_tot_ql)) then
156  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_ql)
157  else if (name .eq. "tend_tabs_simplecloud_profile_total_local" .and. allocated(tend_pr_tot_tabs)) then
158  call set_published_field_value(field_value, real_1d_field=tend_pr_tot_tabs)
159  end if
160 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ finalisation_callback()

subroutine simplecloud_mod::finalisation_callback ( type(model_state_type), intent(inout), target  current_state)
private

Definition at line 248 of file simplecloud.F90.

249  type(model_state_type), target, intent(inout) :: current_state
250 
251  if (allocated(tend_3d_th)) deallocate(tend_3d_th)
252  if (allocated(tend_3d_qv)) deallocate(tend_3d_qv)
253  if (allocated(tend_3d_ql)) deallocate(tend_3d_ql)
254  if (allocated(tend_3d_tabs)) deallocate(tend_3d_tabs)
255 
256  if (allocated(tend_pr_tot_th)) deallocate(tend_pr_tot_th)
257  if (allocated(tend_pr_tot_qv)) deallocate(tend_pr_tot_qv)
258  if (allocated(tend_pr_tot_ql)) deallocate(tend_pr_tot_ql)
259  if (allocated(tend_pr_tot_tabs)) deallocate(tend_pr_tot_tabs)
260 
Here is the caller graph for this function:

◆ initialisation_callback()

subroutine simplecloud_mod::initialisation_callback ( type(model_state_type), intent(inout), target  current_state)
private

Definition at line 164 of file simplecloud.F90.

165  type(model_state_type), target, intent(inout) :: current_state
166 
167  integer :: k ! look counter
168  logical :: l_qdiag
169 
170  if (is_component_enabled(current_state%options_database, "casim")) then
171  call log_master_log(log_error, "Casim and Simplecloud are enabled, this does not work yet. Please disable one")
172  end if
173 
174  iqv=get_q_index(standard_q_names%VAPOUR, 'simplecloud')
175  iql=get_q_index(standard_q_names%CLOUD_LIQUID_MASS, 'simplecloud')
176 
177  ! set buoyancy coefficient (value for vapour should be set
178  ! elsewhere for a moist model
179  if (.not. allocated(current_state%cq))then
180  allocate(current_state%cq(current_state%number_q_fields))
181  current_state%cq=0.0_default_precision
182  end if
183  current_state%cq(iql) = -1.0
184 
185  max_height_cloud=options_get_real(current_state%options_database, "max_height_cloud")
186  do k=2, current_state%local_grid%size(z_index)-1
187  if (current_state%global_grid%configuration%vertical%zn(k) > max_height_cloud) exit
188  end do
189  k_cloudmax=k-1
190 
191  ! Set tendency diagnostic logicals based on availability
192  ! Need to use 3d tendencies to compute the profiles, so they will be allocated
193  ! in the case where profiles are available
194  l_qdiag = (.not. current_state%passive_q .and. current_state%number_q_fields .gt. 0)
195 
196  l_tend_pr_tot_th = current_state%th%active
197  l_tend_pr_tot_qv = l_qdiag .and. current_state%number_q_fields .ge. 1
198  l_tend_pr_tot_ql = l_qdiag .and. current_state%number_q_fields .ge. 2
199  l_tend_pr_tot_tabs = l_tend_pr_tot_th
200 
201  l_tend_3d_th = current_state%th%active .or. l_tend_pr_tot_th
202  l_tend_3d_qv = (l_qdiag .and. current_state%number_q_fields .ge. 1) .or. l_tend_pr_tot_qv
203  l_tend_3d_ql = (l_qdiag .and. current_state%number_q_fields .ge. 2) .or. l_tend_pr_tot_ql
204  l_tend_3d_tabs = l_tend_3d_th
205 
206  ! Allocate 3d tendency fields upon availability
207  if (l_tend_3d_th) then
208  allocate( tend_3d_th(current_state%local_grid%size(z_index), &
209  current_state%local_grid%size(y_index), &
210  current_state%local_grid%size(x_index) ) )
211  endif
212  if (l_tend_3d_qv) then
213  allocate( tend_3d_qv(current_state%local_grid%size(z_index), &
214  current_state%local_grid%size(y_index), &
215  current_state%local_grid%size(x_index) ) )
216  endif
217  if (l_tend_3d_ql) then
218  allocate( tend_3d_ql(current_state%local_grid%size(z_index), &
219  current_state%local_grid%size(y_index), &
220  current_state%local_grid%size(x_index) ) )
221  endif
222  if (l_tend_3d_tabs) then
223  allocate( tend_3d_tabs(current_state%local_grid%size(z_index), &
224  current_state%local_grid%size(y_index), &
225  current_state%local_grid%size(x_index) ) )
226  endif
227 
228  ! Allocate profile tendency fields upon availability
229  if (l_tend_pr_tot_th) then
230  allocate( tend_pr_tot_th(current_state%local_grid%size(z_index)) )
231  endif
232  if (l_tend_pr_tot_qv) then
233  allocate( tend_pr_tot_qv(current_state%local_grid%size(z_index)) )
234  endif
235  if (l_tend_pr_tot_ql) then
236  allocate( tend_pr_tot_ql(current_state%local_grid%size(z_index)) )
237  endif
238  if (l_tend_pr_tot_tabs) then
239  allocate( tend_pr_tot_tabs(current_state%local_grid%size(z_index)) )
240  endif
241 
242  ! Save the sampling_frequency to force diagnostic calculation on select time steps
243  diagnostic_generation_frequency=options_get_integer(current_state%options_database, "sampling_frequency")
244 
Here is the caller graph for this function:

◆ save_precomponent_tendencies()

subroutine simplecloud_mod::save_precomponent_tendencies ( type(model_state_type), intent(in), target  current_state,
integer, intent(in)  cxn,
integer, intent(in)  cyn,
integer, intent(in)  txn,
integer, intent(in)  tyn 
)
private

Save the 3d tendencies coming into the component.

Parameters
current_stateCurrent model state
cxnThe current slice, x, index
cynThe current column, y, index.
txntarget_x_index
tyntarget_y_index

Definition at line 394 of file simplecloud.F90.

395  type(model_state_type), target, intent(in) :: current_state
396  integer, intent(in) :: cxn, cyn, txn, tyn
397 
398  ! Save 3d tendency fields upon request (of 3d or profiles) and availability
399  if (l_tend_3d_th) then
400  tend_3d_th(:,tyn,txn)=current_state%sth%data(:,cyn,cxn)
401  endif
402  if (l_tend_3d_qv) then
403  tend_3d_qv(:,tyn,txn)=current_state%sq(iqv)%data(:,cyn,cxn)
404  endif
405  if (l_tend_3d_ql) then
406  tend_3d_ql(:,tyn,txn)=current_state%sq(iql)%data(:,cyn,cxn)
407  endif
408  if (l_tend_3d_tabs) then
409  tend_3d_tabs(:,tyn,txn)=current_state%sth%data(:,cyn,cxn) * current_state%global_grid%configuration%vertical%rprefrcp(:)
410  endif
411 
Here is the caller graph for this function:

◆ set_published_field_value()

subroutine simplecloud_mod::set_published_field_value ( type(component_field_value_type), intent(inout)  field_value,
real(kind=default_precision), dimension(:), optional  real_1d_field,
real(kind=default_precision), dimension(:,:), optional  real_2d_field,
real(kind=default_precision), dimension(:,:,:), optional  real_3d_field 
)
private

Sets the published field value from the temporary diagnostic values held by this component.

Parameters
field_valuePopulated with the value of the field
real_1d_fieldOptional one dimensional real of values to publish
real_2d_fieldOptional two dimensional real of values to publish

Definition at line 462 of file simplecloud.F90.

463  type(component_field_value_type), intent(inout) :: field_value
464  real(kind=default_precision), dimension(:), optional :: real_1d_field
465  real(kind=default_precision), dimension(:,:), optional :: real_2d_field
466  real(kind=default_precision), dimension(:,:,:), optional :: real_3d_field
467 
468  if (present(real_1d_field)) then
469  allocate(field_value%real_1d_array(size(real_1d_field)), source=real_1d_field)
470  else if (present(real_2d_field)) then
471  allocate(field_value%real_2d_array(size(real_2d_field, 1), size(real_2d_field, 2)), source=real_2d_field)
472  else if (present(real_3d_field)) then
473  allocate(field_value%real_3d_array(size(real_3d_field, 1), size(real_3d_field, 2), size(real_3d_field, 3)), &
474  source=real_3d_field)
475  end if
Here is the caller graph for this function:

◆ simplecloud_get_descriptor()

type(component_descriptor_type) function, public simplecloud_mod::simplecloud_get_descriptor

Provides the descriptor back to the caller and is used in component registration.

Returns
The termination check component descriptor

Definition at line 46 of file simplecloud.F90.

47  simplecloud_get_descriptor%name="simplecloud"
48  simplecloud_get_descriptor%version=0.1
49  simplecloud_get_descriptor%initialisation=>initialisation_callback
50  simplecloud_get_descriptor%timestep=>timestep_callback
51  simplecloud_get_descriptor%finalisation=>finalisation_callback
52 
53  simplecloud_get_descriptor%field_value_retrieval=>field_value_retrieval_callback
54  simplecloud_get_descriptor%field_information_retrieval=>field_information_retrieval_callback
55  allocate(simplecloud_get_descriptor%published_fields(4+4))
56 
57  simplecloud_get_descriptor%published_fields(1)="tend_th_simplecloud_3d_local"
58  simplecloud_get_descriptor%published_fields(2)="tend_qv_simplecloud_3d_local"
59  simplecloud_get_descriptor%published_fields(3)="tend_ql_simplecloud_3d_local"
60  simplecloud_get_descriptor%published_fields(4)="tend_tabs_simplecloud_3d_local"
61 
62  simplecloud_get_descriptor%published_fields(4+1)="tend_th_simplecloud_profile_total_local"
63  simplecloud_get_descriptor%published_fields(4+2)="tend_qv_simplecloud_profile_total_local"
64  simplecloud_get_descriptor%published_fields(4+3)="tend_ql_simplecloud_profile_total_local"
65  simplecloud_get_descriptor%published_fields(4+4)="tend_tabs_simplecloud_profile_total_local"
66 
Here is the call graph for this function:

◆ timestep_callback()

subroutine simplecloud_mod::timestep_callback ( type(model_state_type), intent(inout), target  current_state)
private

Called for each column per timestep this will apply a forcing term to the aerosol fields.

Parameters
current_stateThe current model state

Definition at line 267 of file simplecloud.F90.

268  type(model_state_type), target, intent(inout) :: current_state
269 
270  real(DEFAULT_PRECISION) :: TdegK ! Temperature in Kelvin
271  real(DEFAULT_PRECISION) :: Pmb ! Pressure in mb
272  real(DEFAULT_PRECISION) :: exner ! Exner pressure
273  real(DEFAULT_PRECISION) :: one_over_exner ! Reciprocal of Exner pressure
274  real(DEFAULT_PRECISION) :: qv,qc ! Shorthand for vapour and cloud mass mixing ratio
275  real(DEFAULT_PRECISION) :: qs ! Saturation mixing ratio
276  real(DEFAULT_PRECISION) :: dqsdT ! Rate of change of qs with temperature
277  real(DEFAULT_PRECISION) :: qsatfac ! Multiplicative factor
278  real(DEFAULT_PRECISION) :: dmass ! Mass transfer mixing ratio
279 
280  integer :: k ! Loop counter
281  integer :: icol, jcol ! Shorthand column indices
282 
283  real(DEFAULT_PRECISION) :: dtm ! Local timestep variable
284  integer :: target_x_index, target_y_index
285 
286  ! Zero profile tendency totals on first instance in the sum
287  if (current_state%first_timestep_column) then
288  if (l_tend_pr_tot_th) then
289  tend_pr_tot_th(:)=0.0_default_precision
290  endif
291  if (l_tend_pr_tot_qv) then
292  tend_pr_tot_qv(:)=0.0_default_precision
293  endif
294  if (l_tend_pr_tot_ql) then
295  tend_pr_tot_ql(:)=0.0_default_precision
296  endif
297  if (l_tend_pr_tot_tabs) then
298  tend_pr_tot_tabs(:)=0.0_default_precision
299  endif
300  endif ! zero totals
301 
302 
303  if (current_state%halo_column) return
304 
305 
306  dtm = current_state%dtm*2.0
307  if (current_state%field_stepping == forward_stepping) dtm=current_state%dtm! Should this be revised to scalar_stepping
308 
309  icol=current_state%column_local_x
310  jcol=current_state%column_local_y
311  target_y_index=jcol-current_state%local_grid%halo_size(y_index)
312  target_x_index=icol-current_state%local_grid%halo_size(x_index)
313 
314  if (mod(current_state%timestep, diagnostic_generation_frequency) == 0) then
315  call save_precomponent_tendencies(current_state, icol, jcol, target_x_index, target_y_index)
316  end if
317 
318  do k=2,k_cloudmax
319 
320  exner = current_state%global_grid%configuration%vertical%rprefrcp(k)
321  one_over_exner = current_state%global_grid%configuration%vertical%prefrcp(k)
322  pmb = (current_state%global_grid%configuration%vertical%prefn(k)/100.)
323 
324  if (current_state%field_stepping == forward_stepping) then ! Should this be revised to scalar_stepping
325  qv = current_state%q(iqv)%data(k, jcol, icol) + current_state%sq(iqv)%data(k, jcol, icol)*dtm
326  qc = current_state%q(iql)%data(k, jcol, icol) + current_state%sq(iql)%data(k, jcol, icol)*dtm
327  tdegk = (current_state%th%data(k, jcol, icol) + current_state%sth%data(k, jcol, icol)*dtm &
328  + current_state%global_grid%configuration%vertical%thref(k))*exner
329  else
330  qv = current_state%zq(iqv)%data(k, jcol, icol) + current_state%sq(iqv)%data(k, jcol, icol)*dtm
331  qc = current_state%zq(iql)%data(k, jcol, icol) + current_state%sq(iql)%data(k, jcol, icol)*dtm
332  tdegk = (current_state%zth%data(k, jcol, icol) + current_state%sth%data(k, jcol, icol)*dtm &
333  + current_state%global_grid%configuration%vertical%thref(k))*exner
334  end if
335  ! Calculate the cloud/vapour increments
336 
337  qs = qsaturation(tdegk, pmb)
338 
339  if (qv > qs .or. qc >0.0)then
340  dqsdt = dqwsatdt(qs, tdegk)
341 
342  qsatfac = 1.0/(1.0 + rlvap_over_cp*dqsdt)
343 
344  dmass = max(-qc,(qv-qs)*qsatfac)/dtm
345 
346  current_state%sq(iqv)%data(k, jcol, icol) = current_state%sq(iqv)%data(k, jcol, icol) - dmass
347  current_state%sq(iql)%data(k, jcol, icol) = current_state%sq(iql)%data(k, jcol, icol) + dmass
348 
349  current_state%sth%data(k, jcol, icol) = current_state%sth%data(k, jcol, icol) &
350  + rlvap_over_cp*dmass*one_over_exner
351 
352  end if
353 
354  end do
355 
356  ! If there's any cloud above then evaporate it
357  do k=k_cloudmax+1, current_state%local_grid%size(z_index)
358  if (current_state%scalar_stepping == forward_stepping) then
359  qv = current_state%q(iqv)%data(k, jcol, icol) + current_state%sq(iqv)%data(k, jcol, icol)*dtm
360  qc = current_state%q(iql)%data(k, jcol, icol) + current_state%sq(iql)%data(k, jcol, icol)*dtm
361  tdegk = (current_state%th%data(k, jcol, icol) + current_state%sth%data(k, jcol, icol)*dtm &
362  + current_state%global_grid%configuration%vertical%thref(k))*exner
363  else
364  qv = current_state%zq(iqv)%data(k, jcol, icol) + current_state%sq(iqv)%data(k, jcol, icol)*dtm
365  qc = current_state%zq(iql)%data(k, jcol, icol) + current_state%sq(iql)%data(k, jcol, icol)*dtm
366  tdegk = (current_state%zth%data(k, jcol, icol) + current_state%sth%data(k, jcol, icol)*dtm &
367  + current_state%global_grid%configuration%vertical%thref(k))*exner
368  end if
369  if (qc >0.0)then
370  dmass = -qc/dtm
371 
372  current_state%sq(iqv)%data(k, jcol, icol) = current_state%sq(iqv)%data(k, jcol, icol) - dmass
373  current_state%sq(iql)%data(k, jcol, icol) = current_state%sq(iql)%data(k, jcol, icol) + dmass
374 
375  current_state%sth%data(k, jcol, icol) = current_state%sth%data(k, jcol, icol) &
376  + rlvap_over_cp*dmass*one_over_exner
377 
378  end if
379  end do
380 
381  if (mod(current_state%timestep, diagnostic_generation_frequency) == 0) then
382  call compute_component_tendencies(current_state, icol, jcol, target_x_index, target_y_index)
383  end if
384 
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ diagnostic_generation_frequency

integer simplecloud_mod::diagnostic_generation_frequency
private

Definition at line 37 of file simplecloud.F90.

37  integer :: diagnostic_generation_frequency

◆ iql

integer simplecloud_mod::iql
private

Definition at line 23 of file simplecloud.F90.

◆ iqv

integer simplecloud_mod::iqv
private

Definition at line 23 of file simplecloud.F90.

23  integer :: iqv, iql

◆ k_cloudmax

integer simplecloud_mod::k_cloudmax
private

Definition at line 25 of file simplecloud.F90.

25  integer :: k_cloudmax ! max k index for height

◆ l_tend_3d_ql

logical simplecloud_mod::l_tend_3d_ql
private

Definition at line 32 of file simplecloud.F90.

◆ l_tend_3d_qv

logical simplecloud_mod::l_tend_3d_qv
private

Definition at line 32 of file simplecloud.F90.

◆ l_tend_3d_tabs

logical simplecloud_mod::l_tend_3d_tabs
private

Definition at line 32 of file simplecloud.F90.

◆ l_tend_3d_th

logical simplecloud_mod::l_tend_3d_th
private

Definition at line 32 of file simplecloud.F90.

32  logical :: l_tend_3d_th, l_tend_3d_qv, l_tend_3d_ql, l_tend_3d_tabs

◆ l_tend_pr_tot_ql

logical simplecloud_mod::l_tend_pr_tot_ql
private

Definition at line 36 of file simplecloud.F90.

◆ l_tend_pr_tot_qv

logical simplecloud_mod::l_tend_pr_tot_qv
private

Definition at line 36 of file simplecloud.F90.

◆ l_tend_pr_tot_tabs

logical simplecloud_mod::l_tend_pr_tot_tabs
private

Definition at line 36 of file simplecloud.F90.

◆ l_tend_pr_tot_th

logical simplecloud_mod::l_tend_pr_tot_th
private

Definition at line 36 of file simplecloud.F90.

36  logical :: l_tend_pr_tot_th,l_tend_pr_tot_qv,l_tend_pr_tot_ql,l_tend_pr_tot_tabs

◆ max_height_cloud

real(kind=default_precision) simplecloud_mod::max_height_cloud
private

Definition at line 26 of file simplecloud.F90.

26  real(kind=default_precision) :: max_height_cloud

◆ tend_3d_ql

real(kind=default_precision), dimension(:,:,:), allocatable simplecloud_mod::tend_3d_ql
private

Definition at line 30 of file simplecloud.F90.

◆ tend_3d_qv

real(kind=default_precision), dimension(:,:,:), allocatable simplecloud_mod::tend_3d_qv
private

Definition at line 30 of file simplecloud.F90.

◆ tend_3d_tabs

real(kind=default_precision), dimension(:,:,:), allocatable simplecloud_mod::tend_3d_tabs
private

Definition at line 30 of file simplecloud.F90.

◆ tend_3d_th

real(kind=default_precision), dimension(:,:,:), allocatable simplecloud_mod::tend_3d_th
private

Definition at line 30 of file simplecloud.F90.

30  real(kind=default_precision), dimension(:,:,:), allocatable :: &
31  tend_3d_th, tend_3d_qv, tend_3d_ql, tend_3d_tabs

◆ tend_pr_tot_ql

real(kind=default_precision), dimension(:), allocatable simplecloud_mod::tend_pr_tot_ql
private

Definition at line 34 of file simplecloud.F90.

◆ tend_pr_tot_qv

real(kind=default_precision), dimension(:), allocatable simplecloud_mod::tend_pr_tot_qv
private

Definition at line 34 of file simplecloud.F90.

◆ tend_pr_tot_tabs

real(kind=default_precision), dimension(:), allocatable simplecloud_mod::tend_pr_tot_tabs
private

Definition at line 34 of file simplecloud.F90.

◆ tend_pr_tot_th

real(kind=default_precision), dimension(:), allocatable simplecloud_mod::tend_pr_tot_th
private

Definition at line 34 of file simplecloud.F90.

34  real(kind=default_precision), dimension(:), allocatable :: &
35  tend_pr_tot_th, tend_pr_tot_qv, tend_pr_tot_ql, tend_pr_tot_tabs
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
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
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
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
datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17