MONC
Functions/Subroutines | Variables
casim_mod Module Reference

Implimentation of CASIM microphysics. More...

Functions/Subroutines

type(component_descriptor_type) function, public casim_get_descriptor ()
 Provides the descriptor back to the caller and is used in component registration. More...
 
subroutine initialisation_callback (current_state)
 The initialisation callback sets up the microphysics. More...
 
subroutine timestep_callback (current_state)
 Called for each column per timestep this will calculate the microphysical tendencies. More...
 
subroutine read_configuration (current_state)
 
subroutine field_information_retrieval_callback (current_state, name, field_information)
 
subroutine field_value_retrieval_callback (current_state, name, field_value)
 Field value retrieval callback, this returns the value of a specific published field. More...
 

Variables

real(wp), dimension(:,:,:), allocatable theta
 
real(wp), dimension(:,:,:), allocatable pressure
 
real(wp), dimension(:,:,:), allocatable z_half
 
real(wp), dimension(:,:,:), allocatable z_centre
 
real(wp), dimension(:,:,:), allocatable dz
 
real(wp), dimension(:,:,:), allocatable qv
 
real(wp), dimension(:,:,:), allocatable qc
 
real(wp), dimension(:,:,:), allocatable nc
 
real(wp), dimension(:,:,:), allocatable qr
 
real(wp), dimension(:,:,:), allocatable nr
 
real(wp), dimension(:,:,:), allocatable m3r
 
real(wp), dimension(:,:,:), allocatable rho
 
real(wp), dimension(:,:,:), allocatable exner
 
real(wp), dimension(:,:,:), allocatable w
 
real(wp), dimension(:,:,:), allocatable tke
 
real(wp), dimension(:,:,:), allocatable qi
 
real(wp), dimension(:,:,:), allocatable ni
 
real(wp), dimension(:,:,:), allocatable qs
 
real(wp), dimension(:,:,:), allocatable ns
 
real(wp), dimension(:,:,:), allocatable m3s
 
real(wp), dimension(:,:,:), allocatable qg
 
real(wp), dimension(:,:,:), allocatable ng
 
real(wp), dimension(:,:,:), allocatable m3g
 
real(wp), dimension(:,:,:), allocatable accumsolmass
 
real(wp), dimension(:,:,:), allocatable accumsolnumber
 
real(wp), dimension(:,:,:), allocatable activesolliquid
 
real(wp), dimension(:,:,:), allocatable aitkensolmass
 
real(wp), dimension(:,:,:), allocatable aitkensolnumber
 
real(wp), dimension(:,:,:), allocatable coarsesolmass
 
real(wp), dimension(:,:,:), allocatable coarsesolnumber
 
real(wp), dimension(:,:,:), allocatable activesolrain
 
real(wp), dimension(:,:,:), allocatable coarsedustmass
 
real(wp), dimension(:,:,:), allocatable coarsedustnumber
 
real(wp), dimension(:,:,:), allocatable activeinsolice
 
real(wp), dimension(:,:,:), allocatable activesolice
 
real(wp), dimension(:,:,:), allocatable activeinsolliquid
 
real(wp), dimension(:,:,:), allocatable accuminsolmass
 
real(wp), dimension(:,:,:), allocatable accuminsolnumber
 
real(wp), dimension(:,:,:), allocatable activesolnumber
 
real(wp), dimension(:,:,:), allocatable activeinsolnumber
 
real(wp), dimension(:,:,:), allocatable aitkensolbk
 
real(wp), dimension(:,:,:), allocatable accumsolbk
 
real(wp), dimension(:,:,:), allocatable coarsesolbk
 
real(wp), dimension(:,:,:), allocatable dqv
 
real(wp), dimension(:,:,:), allocatable dth
 
real(wp), dimension(:,:,:), allocatable dqc
 
real(wp), dimension(:,:,:), allocatable dnc
 
real(wp), dimension(:,:,:), allocatable dqr
 
real(wp), dimension(:,:,:), allocatable dnr
 
real(wp), dimension(:,:,:), allocatable dm3r
 
real(wp), dimension(:,:,:), allocatable dqi
 
real(wp), dimension(:,:,:), allocatable dni
 
real(wp), dimension(:,:,:), allocatable dqs
 
real(wp), dimension(:,:,:), allocatable dns
 
real(wp), dimension(:,:,:), allocatable dm3s
 
real(wp), dimension(:,:,:), allocatable dqg
 
real(wp), dimension(:,:,:), allocatable dng
 
real(wp), dimension(:,:,:), allocatable dm3g
 
real(wp), dimension(:,:,:), allocatable daccumsolmass
 
real(wp), dimension(:,:,:), allocatable daccumsolnumber
 
real(wp), dimension(:,:,:), allocatable dactivesolliquid
 
real(wp), dimension(:,:,:), allocatable daitkensolmass
 
real(wp), dimension(:,:,:), allocatable daitkensolnumber
 
real(wp), dimension(:,:,:), allocatable dcoarsesolmass
 
real(wp), dimension(:,:,:), allocatable dcoarsesolnumber
 
real(wp), dimension(:,:,:), allocatable dactivesolrain
 
real(wp), dimension(:,:,:), allocatable dcoarsedustmass
 
real(wp), dimension(:,:,:), allocatable dcoarsedustnumber
 
real(wp), dimension(:,:,:), allocatable dactiveinsolice
 
real(wp), dimension(:,:,:), allocatable dactivesolice
 
real(wp), dimension(:,:,:), allocatable dactiveinsolliquid
 
real(wp), dimension(:,:,:), allocatable daccuminsolmass
 
real(wp), dimension(:,:,:), allocatable daccuminsolnumber
 
real(wp), dimension(:,:,:), allocatable dactivesolnumber
 
real(wp), dimension(:,:,:), allocatable dactiveinsolnumber
 
real(wp), dimension(:,:), allocatable surface_precip
 
integer ils
 
integer ile
 
integer jls
 
integer jle
 
integer kls
 
integer kle
 
integer its
 
integer ite
 
integer jts
 
integer jte
 
integer kts
 
integer kte
 
integer iqv =0
 
integer iql =0
 
integer iqr =0
 
integer iqi =0
 
integer iqs =0
 
integer iqg =0
 
integer inl =0
 
integer inr =0
 
integer ini =0
 
integer ins =0
 
integer ing =0
 
integer i3mr =0
 
integer i3ms =0
 
integer i3mg =0
 
integer i_accumsolmass =0
 
integer i_accumsolnumber =0
 
integer i_activesolliquid =0
 
integer i_aitkensolmass =0
 
integer i_aitkensolnumber =0
 
integer i_coarsesolmass =0
 
integer i_coarsesolnumber =0
 
integer i_activesolrain =0
 
integer i_coarsedustmass =0
 
integer i_coarsedustnumber =0
 
integer i_activeinsolice =0
 
integer i_activesolice =0
 
integer i_activeinsolliquid =0
 
integer i_accuminsolmass =0
 
integer i_accuminsolnumber =0
 
integer i_activesolnumber =0
 
integer i_activeinsolnumber =0
 
real(kind=default_precision), dimension(:), allocatable phomc_tot
 
real(kind=default_precision), dimension(:), allocatable pinuc_tot
 
real(kind=default_precision), dimension(:), allocatable pidep_tot
 
real(kind=default_precision), dimension(:), allocatable psdep_tot
 
real(kind=default_precision), dimension(:), allocatable piacw_tot
 
real(kind=default_precision), dimension(:), allocatable psacw_tot
 
real(kind=default_precision), dimension(:), allocatable psacr_tot
 
real(kind=default_precision), dimension(:), allocatable pisub_tot
 
real(kind=default_precision), dimension(:), allocatable pssub_tot
 
real(kind=default_precision), dimension(:), allocatable pimlt_tot
 
real(kind=default_precision), dimension(:), allocatable psmlt_tot
 
real(kind=default_precision), dimension(:), allocatable psaut_tot
 
real(kind=default_precision), dimension(:), allocatable psaci_tot
 
real(kind=default_precision), dimension(:), allocatable praut_tot
 
real(kind=default_precision), dimension(:), allocatable pracw_tot
 
real(kind=default_precision), dimension(:), allocatable prevp_tot
 
real(kind=default_precision), dimension(:), allocatable pgacw_tot
 
real(kind=default_precision), dimension(:), allocatable pgacs_tot
 
real(kind=default_precision), dimension(:), allocatable pgmlt_tot
 
real(kind=default_precision), dimension(:), allocatable pgsub_tot
 
real(kind=default_precision), dimension(:), allocatable psedi_tot
 
real(kind=default_precision), dimension(:), allocatable pseds_tot
 
real(kind=default_precision), dimension(:), allocatable psedr_tot
 
real(kind=default_precision), dimension(:), allocatable psedg_tot
 
real(kind=default_precision), dimension(:), allocatable psedl_tot
 
real(kind=default_precision), dimension(:), allocatable pcond_tot
 

Detailed Description

Implimentation of CASIM microphysics.

Dummy stub when not compiling with CASIM microphysics.

Function/Subroutine Documentation

◆ casim_get_descriptor()

type(component_descriptor_type) function, public casim_mod::casim_get_descriptor

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

Returns
The termination check component descriptor

Definition at line 178 of file casim.F90.

179  casim_get_descriptor%name="casim"
180  casim_get_descriptor%version=0.1
181  casim_get_descriptor%initialisation=>initialisation_callback
182  casim_get_descriptor%timestep=>timestep_callback
183 
184  ! Set up fields to be published for diagnostics. These are made available to
185  ! IO server in the field_value_retrieval_callback at the end of this module
186  !
187  casim_get_descriptor%field_value_retrieval=>field_value_retrieval_callback
188  casim_get_descriptor%field_information_retrieval=>field_information_retrieval_callback
189 
190  allocate(casim_get_descriptor%published_fields(27))
191 
192  casim_get_descriptor%published_fields(1)="surface_precip"
193  casim_get_descriptor%published_fields(2)="homogeneous_freezing_rate"
194  casim_get_descriptor%published_fields(3)="ice_nucleations_rate"
195  casim_get_descriptor%published_fields(4)="ice_deposition_rate"
196  casim_get_descriptor%published_fields(5)="snow_deposition_rate"
197  casim_get_descriptor%published_fields(6)="ice_acc_cloud_rate"
198  casim_get_descriptor%published_fields(7)="snow_acc_cloud_rate"
199  casim_get_descriptor%published_fields(8)="snow_acc_rain_rate"
200  casim_get_descriptor%published_fields(9)="ice_sublime_rate"
201  casim_get_descriptor%published_fields(10)="snow_sublime_rate"
202  casim_get_descriptor%published_fields(11)="ice_melt_rate"
203  casim_get_descriptor%published_fields(12)="snow_melt_rate"
204  casim_get_descriptor%published_fields(13)="snow_autoconversion_rate"
205  casim_get_descriptor%published_fields(14)="snow_acc_ice_rate"
206  casim_get_descriptor%published_fields(15)="rain_autoconversion_rate"
207  casim_get_descriptor%published_fields(16)="rain_acc_cloud_rate"
208  casim_get_descriptor%published_fields(17)="rain_evap_rate"
209  casim_get_descriptor%published_fields(18)="graup_acc_cloud_rate"
210  casim_get_descriptor%published_fields(19)="graup_acc_snow_rate"
211  casim_get_descriptor%published_fields(20)="graup_melt_rate"
212  casim_get_descriptor%published_fields(21)="graup_sublime_rate"
213  casim_get_descriptor%published_fields(22)="ice_sed_rate"
214  casim_get_descriptor%published_fields(23)="snow_sed_rate"
215  casim_get_descriptor%published_fields(24)="rain_sed_rate"
216  casim_get_descriptor%published_fields(25)="graup_sed_rate"
217  casim_get_descriptor%published_fields(26)="cloud_sed_rate"
218  casim_get_descriptor%published_fields(27)="condensation_rate"
219 
Here is the call graph for this function:

◆ field_information_retrieval_callback()

subroutine casim_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 
)

Definition at line 953 of file casim.F90.

954  type(model_state_type), target, intent(inout) :: current_state
955  character(len=*), intent(in) :: name
956  type(component_field_information_type), intent(out) :: field_information
957 
958  field_information%field_type=component_array_field_type
959  field_information%data_type=component_double_data_type
960  if (name .eq. "surface_precip") then
961  field_information%number_dimensions=2
962  field_information%dimension_sizes(1)=current_state%local_grid%size(y_index)
963  field_information%dimension_sizes(2)=current_state%local_grid%size(x_index)
964  !else if (name .eq. "pcond_total" .or. name .eq. "psedl_total") then
965  ! field_information%number_dimensions=1
966  ! field_information%dimension_sizes(1)=current_state%local_grid%size(Z_INDEX)
967  else
968  field_information%number_dimensions=3
969  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
970  field_information%dimension_sizes(2)=current_state%local_grid%size(y_index)
971  field_information%dimension_sizes(3)=current_state%local_grid%size(x_index)
972  endif
973 
974  field_information%enabled=.true.
975 
Here is the caller graph for this function:

◆ field_value_retrieval_callback()

subroutine casim_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

Field value retrieval callback, this returns the value of a specific published field.

Parameters
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 982 of file casim.F90.

983  type(model_state_type), target, intent(inout) :: current_state
984  character(len=*), intent(in) :: name
985  type(component_field_value_type), intent(out) :: field_value
986 
987  integer :: i
988 
989  if (name .eq. "surface_precip") then
990  allocate(field_value%real_2d_array(current_state%local_grid%size(y_index), &
991  current_state%local_grid%size(x_index)))
992  field_value%real_2d_array(:,:)= surface_precip(:,:)
993  else if (name .eq. "condensation_rate") then
994  allocate(field_value%real_3d_array(current_state%local_grid%size(z_index), &
995  current_state%local_grid%size(y_index), &
996  current_state%local_grid%size(x_index)))
997  field_value%real_3d_array(:,:,:) = casim_monc_dgs % pcond(:,:,:)
998 !!$ else if (name .eq. "pcond_total") then
999 !!$ allocate(field_value%real_1d_array(current_state%local_grid%size(Z_INDEX)))
1000 !!$ field_value%real_1d_array(:)=pcond_tot(:)
1001  end if
1002 
Here is the caller graph for this function:

◆ initialisation_callback()

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

The initialisation callback sets up the microphysics.

Parameters
current_stateThe current model state

Set up and allocate the local arrays

Definition at line 224 of file casim.F90.

225  type(model_state_type), target, intent(inout) :: current_state
226 
227  integer :: y_size_local, x_size_local
228 
229  if (is_component_enabled(current_state%options_database, "simplecloud")) then
230  call log_master_log(log_error, "Casim and Simplecloud are enabled, this does not work yet. Please disable one")
231  end if
232 
233  !allocate(psedl_tot(current_state%local_grid%size(Z_INDEX)), &
234  ! pcond_tot(current_state%local_grid%size(Z_INDEX)))
235 
236  y_size_local = current_state%local_grid%size(y_index)
237  x_size_local = current_state%local_grid%size(x_index)
238 
239  call read_configuration(current_state)
240 
241  ils=1
242  ile=1
243  jls=1
244  jle=1
245  kls=2
246  kle=current_state%local_grid%size(z_index)
247  its=1
248  ite=1
249  jts=1
250  jte=1
251  kts=1
252  kte=current_state%local_grid%size(z_index)
253 
255 
256  allocate(pressure(kte,1,1))
257  allocate(z_half(0:kte,1,1))
258  allocate(z_centre(kte,1,1))
259  allocate(dz(kte,1,1))
260  allocate(rho(kte,1,1))
261  allocate(exner(kte,1,1))
262  allocate(w(kte,1,1))
263  allocate(tke(kte,1,1))
264 
265  allocate(theta(kte,1,1))
266  allocate(qv(kte,1,1))
267  allocate(qc(kte,1,1))
268  allocate(nc(kte,1,1))
269  allocate(qr(kte,1,1))
270  allocate(nr(kte,1,1))
271  allocate(m3r(kte,1,1))
272  allocate(qi(kte,1,1))
273  allocate(ni(kte,1,1))
274  allocate(qs(kte,1,1))
275  allocate(ns(kte,1,1))
276  allocate(m3s(kte,1,1))
277  allocate(qg(kte,1,1))
278  allocate(ng(kte,1,1))
279  allocate(m3g(kte,1,1))
280 
281  allocate(accumsolmass(kte,1,1))
282  allocate(accumsolnumber(kte,1,1))
283  allocate(activesolliquid(kte,1,1))
284  allocate(aitkensolmass(kte,1,1))
285  allocate(aitkensolnumber(kte,1,1))
286  allocate(coarsesolmass(kte,1,1))
287  allocate(coarsesolnumber(kte,1,1))
288  allocate(activesolrain(kte,1,1))
289  allocate(coarsedustmass(kte,1,1))
290  allocate(coarsedustnumber(kte,1,1))
291  allocate(activeinsolice(kte,1,1))
292  allocate(activesolice(kte,1,1))
293  allocate(activeinsolliquid(kte,1,1))
294  allocate(accuminsolmass(kte,1,1))
295  allocate(accuminsolnumber(kte,1,1))
296  allocate(activesolnumber(kte,1,1))
297  allocate(activeinsolnumber(kte,1,1))
298  ! allocate the hygoscopicity arrays
299  allocate(aitkensolbk(kte,1,1))
300  allocate(accumsolbk(kte,1,1))
301  allocate(coarsesolbk(kte,1,1))
302 
303  allocate(dth(kte,1,1))
304  allocate(dqv(kte,1,1))
305  allocate(dqc(kte,1,1))
306  allocate(dnc(kte,1,1))
307  allocate(dqr(kte,1,1))
308  allocate(dnr(kte,1,1))
309  allocate(dm3r(kte,1,1))
310  allocate(dqi(kte,1,1))
311  allocate(dni(kte,1,1))
312  allocate(dqs(kte,1,1))
313  allocate(dns(kte,1,1))
314  allocate(dm3s(kte,1,1))
315  allocate(dqg(kte,1,1))
316  allocate(dng(kte,1,1))
317  allocate(dm3g(kte,1,1))
318 
319  allocate(daccumsolmass(kte,1,1))
320  allocate(daccumsolnumber(kte,1,1))
321  allocate(dactivesolliquid(kte,1,1))
322  allocate(daitkensolmass(kte,1,1))
323  allocate(daitkensolnumber(kte,1,1))
324  allocate(dcoarsesolmass(kte,1,1))
325  allocate(dcoarsesolnumber(kte,1,1))
326  allocate(dactivesolrain(kte,1,1))
327  allocate(dcoarsedustmass(kte,1,1))
328  allocate(dcoarsedustnumber(kte,1,1))
329  allocate(dactiveinsolice(kte,1,1))
330  allocate(dactivesolice(kte,1,1))
331  allocate(dactiveinsolliquid(kte,1,1))
332  allocate(daccuminsolmass(kte,1,1))
333  allocate(daccuminsolnumber(kte,1,1))
334  allocate(dactivesolnumber(kte,1,1))
335  allocate(dactiveinsolnumber(kte,1,1))
336 
337  call set_mphys_switches(option,aerosol_option)
338  call mphys_init(its, ite, jts, jte, kts, kte, ils, ile, jls, jle, kls, kle, l_tendency=.true.)
339 
340  ! Need to allocate the appropriate indices, e.g. iqv, iql...
341  ! This needs to be compatible with the rest of the model
342  ! This essentially reproduces the switching in the main microphysics
343  ! code already done above (set_mphys_switches), so could be combined
344  ! once the MONC method has been finalized.
345  ! Note the numbers assigned here may be different from those assigned
346  ! in the microphysics since we share the q array with other components.
347 
348  if (.not. allocated(current_state%cq))then
349  allocate(current_state%cq(current_state%number_q_fields))
350  current_state%cq=0.0_default_precision
351  end if
352 
353  ! Mass
354  iqv = get_q_index(standard_q_names%VAPOUR, 'casim')
355  if (nq_l>0)then
356  iql = get_q_index(standard_q_names%CLOUD_LIQUID_MASS, 'casim')
357  current_state%cq(iql) = -1.0
358  end if
359  if (nq_r>0)then
360  iqr = get_q_index(standard_q_names%RAIN_MASS, 'casim')
361  current_state%rain_water_mixing_ratio_index=iqr
362  current_state%cq(iqr) = -1.0
363  end if
364  if (.not. l_warm)then
365  if (nq_i>0)then
366  iqi = get_q_index(standard_q_names%ICE_MASS, 'casim')
367  current_state%ice_water_mixing_ratio_index=iqi
368  current_state%cq(iqi) = -1.0
369  end if
370  if (nq_s>0)then
371  iqs = get_q_index(standard_q_names%SNOW_MASS, 'casim')
372  current_state%snow_water_mixing_ratio_index=iqs
373  current_state%cq(iqs) = -1.0
374  end if
375  if (nq_g>0)then
376  iqg = get_q_index(standard_q_names%GRAUPEL_MASS, 'casim')
377  current_state%graupel_water_mixing_ratio_index=iqg
378  current_state%cq(iqg) = -1.0
379  end if
380  end if
381 
382  ! Number
383  if (l_2mc)inl = get_q_index(standard_q_names%CLOUD_LIQUID_NUMBER, 'casim')
384  if (l_2mr)inr = get_q_index(standard_q_names%RAIN_NUMBER, 'casim')
385  if (.not. l_warm)then
386  if (l_2mi)ini = get_q_index(standard_q_names%ICE_NUMBER, 'casim')
387  if (l_2ms)ins = get_q_index(standard_q_names%SNOW_NUMBER, 'casim')
388  if (l_2mg)ing = get_q_index(standard_q_names%GRAUPEL_NUMBER, 'casim')
389  end if
390 
391  ! Third moments
392  if (l_3mr)i3mr = get_q_index(standard_q_names%RAIN_THIRD_MOMENT, 'casim')
393  if (.not. l_warm)then
394  if (l_3ms)i3ms = get_q_index(standard_q_names%SNOW_THIRD_MOMENT, 'casim')
395  if (l_3mg)i3mg = get_q_index(standard_q_names%GRAUPEL_THIRD_MOMENT, 'casim')
396  end if
397 
398  ! Aerosol
399  if (soluble_modes(1) > 1) i_aitkensolmass = &
400  get_q_index(standard_q_names%AITKEN_SOL_MASS, 'casim')
401  if (soluble_modes(1) > 0) i_aitkensolnumber = &
402  get_q_index(standard_q_names%AITKEN_SOL_NUMBER, 'casim')
403  if (soluble_modes(2) > 1) i_accumsolmass = &
404  get_q_index(standard_q_names%ACCUM_SOL_MASS, 'casim')
405  if (soluble_modes(2) > 0) i_accumsolnumber = &
406  get_q_index(standard_q_names%ACCUM_SOL_NUMBER, 'casim')
407  if (soluble_modes(3) > 1) i_coarsesolmass = &
408  get_q_index(standard_q_names%COARSE_SOL_MASS, 'casim')
409  if (soluble_modes(3) > 0) i_coarsesolnumber = &
410  get_q_index(standard_q_names%COARSE_SOL_NUMBER, 'casim')
411  if (active_cloud(isol)) i_activesolliquid = &
412  get_q_index(standard_q_names%ACTIVE_SOL_LIQUID, 'casim')
413  if (active_rain(isol)) i_activesolrain = &
414  get_q_index(standard_q_names%ACTIVE_SOL_RAIN, 'casim')
415  if (insoluble_modes(2) > 1) i_coarsedustmass = &
416  get_q_index(standard_q_names%COARSE_DUST_MASS, 'casim')
417  if (insoluble_modes(2) > 0) i_coarsedustnumber = &
418  get_q_index(standard_q_names%COARSE_DUST_NUMBER, 'casim')
419  if (active_ice(iinsol)) i_activeinsolice = &
420  get_q_index(standard_q_names%ACTIVE_INSOL_ICE, 'casim')
421  if (active_ice(isol)) i_activesolice = &
422  get_q_index(standard_q_names%ACTIVE_SOL_ICE, 'casim')
423  if (active_cloud(iinsol)) i_activeinsolliquid = &
424  get_q_index(standard_q_names%ACTIVE_INSOL_LIQUID, 'casim')
425  if (insoluble_modes(1) > 1) i_accuminsolmass = &
426  get_q_index(standard_q_names%ACCUM_INSOL_MASS, 'casim')
427  if (insoluble_modes(1) > 0) i_accuminsolnumber = &
428  get_q_index(standard_q_names%ACCUM_INSOL_NUMBER, 'casim')
429  if (active_number(isol)) i_activesolnumber = &
430  get_q_index(standard_q_names%ACTIVE_SOL_NUMBER, 'casim')
431  if (active_number(iinsol)) i_activeinsolnumber = &
432  get_q_index(standard_q_names%ACTIVE_INSOL_NUMBER, 'casim')
433 
434  ! set logicals for the microphysics diagnostics: process rates
435  casdiags % l_dth = .true.
436  casdiags % l_dqv = .true.
437  if ( nq_l>0 ) casdiags % l_dqc = .true.
438  if ( nq_r>0 ) casdiags % l_dqr = .true.
439  if ( l_pcond ) casdiags % l_pcond = .true.
440  if ( l_psedl ) then
441  casdiags % l_psedl = .true.
442  casdiags % l_surface_rain = .true.
443  casdiags % l_precip = .true.
444  endif
445  if ( l_praut ) casdiags % l_praut = .true.
446  if ( l_pracw ) casdiags % l_pracw = .true.
447  if ( l_prevp ) casdiags % l_prevp = .true.
448  if ( l_psedr ) then
449  casdiags % l_psedr = .true.
450  casdiags % l_surface_rain = .true.
451  casdiags % l_precip = .true.
452  endif
453  if (.not. l_warm) then
454  if ( nq_i>0 ) casdiags % l_dqi = .true.
455  if ( nq_s>0 ) casdiags % l_dqs = .true.
456  if ( nq_g>0 ) casdiags % l_dqg = .true.
457  if ( l_phomc ) casdiags % l_phomc = .true.
458  if ( l_pinuc ) casdiags % l_pinuc = .true.
459  if ( l_pidep ) casdiags % l_pidep = .true.
460  if ( l_piacw ) casdiags % l_piacw = .true.
461  if ( l_pisub ) casdiags % l_pisub = .true.
462  if ( l_pimlt ) casdiags % l_pimlt = .true.
463  if ( l_psedi ) then
464  casdiags % l_psedi = .true.
465  casdiags % l_surface_snow = .true.
466  casdiags % l_precip = .true.
467  endif
468  if ( l_psmlt ) casdiags % l_psmlt = .true.
469  if ( l_psaut ) casdiags % l_psaut = .true.
470  if ( l_psaci ) casdiags % l_psaci = .true.
471  if ( l_psacw ) casdiags % l_psacw = .true.
472  if ( l_psacr ) casdiags % l_psacr = .true.
473  if ( l_pssub ) casdiags % l_pssub = .true.
474  if ( l_psdep ) casdiags % l_psdep = .true.
475  if ( l_pseds ) then
476  casdiags % l_pseds = .true.
477  casdiags % l_surface_snow = .true.
478  casdiags % l_precip = .true.
479  endif
480  if ( l_pgacw ) casdiags % l_pgacw = .true.
481  if ( l_pgacs ) casdiags % l_pgacs = .true.
482  if ( l_pgmlt ) casdiags % l_pgmlt = .true.
483  if ( l_pgsub ) casdiags % l_pgsub = .true.
484  if ( l_psedg ) then
485  casdiags % l_psedg = .true.
486  casdiags % l_surface_graup = .true.
487  casdiags % l_precip = .true.
488  endif
489  endif
490 
491  ! allocate diagnostic space in casdiags depending on the logicals defined above
492  CALL allocate_diagnostic_space(its, ite, jts, jte, kts, kte)
493  ! this is no longer needed since can use cas_monc_dgs structure but keep for now
494  allocate(surface_precip(y_size_local, x_size_local))
495  ! allocate diagnostic space for MONC fields to export to IO server
496  call allocate_casim_monc_dgs_space(current_state, casdiags)
497 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ read_configuration()

subroutine casim_mod::read_configuration ( type(model_state_type), intent(inout), target  current_state)
private

Definition at line 856 of file casim.F90.

857 
858 
859  Use mphys_parameters, only: p1, p2, p3, sp1, sp2, sp3
860 
861  type(model_state_type), target, intent(inout) :: current_state
862 
863  integer :: ierr
864 
865  option = options_get_integer(current_state%options_database, 'option')
866  diag_mu_option = options_get_integer(current_state%options_database, 'diag_mu_option')
867  iopt_act = options_get_integer(current_state%options_database, 'iopt_act')
868  iopt_inuc = options_get_integer(current_state%options_database, 'iopt_inuc')
869  process_level = options_get_integer(current_state%options_database, 'process_level')
870  aerosol_option = options_get_integer(current_state%options_database, 'aerosol_option')
871  max_step_length = options_get_real(current_state%options_database, 'max_step_length')
872  max_sed_length = options_get_real(current_state%options_database, 'max_sed_length')
873  p1 = options_get_real(current_state%options_database, 'p1')
874  p2 = options_get_real(current_state%options_database, 'p2')
875  p3 = options_get_real(current_state%options_database, 'p3')
876  sp1 = options_get_real(current_state%options_database, 'sp1')
877  sp2 = options_get_real(current_state%options_database, 'sp2')
878  sp3 = options_get_real(current_state%options_database, 'sp3')
879  max_mu = options_get_real(current_state%options_database, 'max_mu')
880  fix_mu = options_get_real(current_state%options_database, 'fix_mu')
881 
882  l_aaut = options_get_logical(current_state%options_database, 'l_aaut')
883  l_aacc = options_get_logical(current_state%options_database, 'l_aacc')
884  l_aevp = options_get_logical(current_state%options_database, 'l_aevp')
885  l_ased = options_get_logical(current_state%options_database, 'l_ased')
886  l_warm = options_get_logical(current_state%options_database, 'l_warm')
887  l_inuc = options_get_logical(current_state%options_database, 'l_inuc')
888  l_iaut = options_get_logical(current_state%options_database, 'l_iaut')
889  l_idep = options_get_logical(current_state%options_database, 'l_idep')
890  l_iacw = options_get_logical(current_state%options_database, 'l_iacw')
891  l_active_inarg2000 = options_get_logical(current_state%options_database, 'l_active_inarg2000')
892  l_separate_rain = options_get_logical(current_state%options_database, 'l_separate_rain')
893  l_sg = options_get_logical(current_state%options_database, 'l_sg')
894  l_g = options_get_logical(current_state%options_database, 'l_g')
895  l_passive = options_get_logical(current_state%options_database, 'l_passive')
896  l_passive3m = options_get_logical(current_state%options_database, 'l_passive3m')
897  l_limit_psd = options_get_logical(current_state%options_database, 'l_limit_psd')
898  l_override_checks = options_get_logical(current_state%options_database, 'l_override_checks')
899  l_raci_g = options_get_logical(current_state%options_database, 'l_raci_g')
900  l_onlycollect = options_get_logical(current_state%options_database, 'l_onlycollect')
901  l_abelshipway = options_get_logical(current_state%options_database, 'l_abelshipway')
902  l_cons = options_get_logical(current_state%options_database, 'l_cons')
903  l_rain = options_get_logical(current_state%options_database, 'l_rain')
904  l_sed_3mdiff = options_get_logical(current_state%options_database, 'l_sed_3mdiff')
905  l_sed_icecloud_as_1m = options_get_logical(current_state%options_database, 'l_sed_icecloud_as_1m')
906  l_tidy_conserve_e = options_get_logical(current_state%options_database, 'l_tidy_conserve_E')
907  l_tidy_conserve_q = options_get_logical(current_state%options_database, 'l_tidy_conserve_q')
908 
909  l_inhom_revp = options_get_logical(current_state%options_database, 'l_inhom_revp')
910  l_pcond = options_get_logical(current_state%options_database, 'l_pcond')
911  l_praut = options_get_logical(current_state%options_database, 'l_praut')
912  l_pracw = options_get_logical(current_state%options_database, 'l_pracw')
913  l_pracr = options_get_logical(current_state%options_database, 'l_pracr')
914  l_prevp = options_get_logical(current_state%options_database, 'l_prevp')
915  l_psedl = options_get_logical(current_state%options_database, 'l_psedl')
916  l_psedr = options_get_logical(current_state%options_database, 'l_psedr')
917  l_ptidy = options_get_logical(current_state%options_database, 'l_ptidy')
918  l_ptidy2 = options_get_logical(current_state%options_database, 'l_ptidy2')
919  l_pinuc = options_get_logical(current_state%options_database, 'l_pinuc')
920  l_pidep = options_get_logical(current_state%options_database, 'l_pidep')
921  l_piacw = options_get_logical(current_state%options_database, 'l_piacw')
922  l_psaut = options_get_logical(current_state%options_database, 'l_psaut')
923  l_psdep = options_get_logical(current_state%options_database, 'l_psdep')
924  l_psacw = options_get_logical(current_state%options_database, 'l_psacw')
925  l_pgdep = options_get_logical(current_state%options_database, 'l_pgdep')
926  l_pseds = options_get_logical(current_state%options_database, 'l_pseds')
927  l_psedi = options_get_logical(current_state%options_database, 'l_psedi')
928  l_psedg = options_get_logical(current_state%options_database, 'l_psedg')
929  l_psaci = options_get_logical(current_state%options_database, 'l_psaci')
930  l_praci = options_get_logical(current_state%options_database, 'l_praci')
931  l_psacr = options_get_logical(current_state%options_database, 'l_psacr')
932  l_pgacr = options_get_logical(current_state%options_database, 'l_pgacr')
933  l_pgacw = options_get_logical(current_state%options_database, 'l_pgacw')
934  l_pgaci = options_get_logical(current_state%options_database, 'l_pgaci')
935  l_pgacs = options_get_logical(current_state%options_database, 'l_pgacs')
936  l_piagg = options_get_logical(current_state%options_database, 'l_piagg')
937  l_psagg = options_get_logical(current_state%options_database, 'l_psagg')
938  l_pgagg = options_get_logical(current_state%options_database, 'l_pgagg')
939  l_psbrk = options_get_logical(current_state%options_database, 'l_psbrk')
940  l_pgshd = options_get_logical(current_state%options_database, 'l_pgshd')
941  l_pihal = options_get_logical(current_state%options_database, 'l_pihal')
942  l_psmlt = options_get_logical(current_state%options_database, 'l_psmlt')
943  l_pgmlt = options_get_logical(current_state%options_database, 'l_pgmlt')
944  l_phomr = options_get_logical(current_state%options_database, 'l_phomr')
945  l_phomc = options_get_logical(current_state%options_database, 'l_phomc')
946  l_pssub = options_get_logical(current_state%options_database, 'l_pssub')
947  l_pgsub = options_get_logical(current_state%options_database, 'l_pgsub')
948  l_pisub = options_get_logical(current_state%options_database, 'l_pisub')
949  l_pimlt = options_get_logical(current_state%options_database, 'l_pimlt')
950 
Here is the caller graph for this function:

◆ timestep_callback()

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

Called for each column per timestep this will calculate the microphysical tendencies.

Parameters
current_stateThe current model state

Definition at line 502 of file casim.F90.

503  type(model_state_type), target, intent(inout) :: current_state
504 
505  REAL(wp) :: dtwp
506  INTEGER :: icol, jcol, iqx, target_x_index, target_y_index
507 
508  icol=current_state%column_local_x
509  jcol=current_state%column_local_y
510  target_y_index=jcol-current_state%local_grid%halo_size(y_index)
511  target_x_index=icol-current_state%local_grid%halo_size(x_index)
512 
513  !if (current_state%first_timestep_column) then
514  ! psedl_tot(:)= 0.0_DEFAULT_PRECISION
515  ! pcond_tot(:)= 0.0_DEFAULT_PRECISION
516  !endif
517 
518  if (current_state%halo_column .or. current_state%timestep < 2) return
519 
520  if (current_state%field_stepping == forward_stepping)then
521  call log_master_log(log_error, 'Currently, CASIM assumes CENTERED_STEPPING')
522  dtwp = current_state%dtm
523  else
524  dtwp = 2.0*current_state%dtm
525  end if
526 
527  ! Initialize aerosol fields to zero...
528  aitkensolmass = 0.0
529  daitkensolmass = 0.0
530  aitkensolnumber = 0.0
531  daitkensolnumber = 0.0
532  accumsolmass = 0.0
533  daccumsolmass = 0.0
534  accumsolnumber = 0.0
535  daccumsolnumber = 0.0
536  coarsesolmass = 0.0
537  dcoarsesolmass = 0.0
538  coarsesolnumber = 0.0
539  dcoarsesolnumber = 0.0
540  activesolliquid = 0.0
541  dactivesolliquid = 0.0
542  coarsedustmass = 0.0
543  dcoarsedustmass = 0.0
544  coarsedustnumber = 0.0
545  dcoarsedustnumber = 0.0
546  activeinsolice = 0.0
547  dactiveinsolice = 0.0
548  activesolice = 0.0
549  dactivesolice = 0.0
550  activeinsolliquid = 0.0
551  dactiveinsolliquid = 0.0
552  accuminsolmass = 0.0
553  daccuminsolmass = 0.0
554  accuminsolnumber = 0.0
555  daccuminsolnumber = 0.0
556  activesolnumber = 0.0
557  dactivesolnumber = 0.0
558  activeinsolnumber = 0.0
559  dactiveinsolnumber = 0.0
560  aitkensolbk = 0.0
561  accumsolbk = 0.0
562  coarsesolbk = 0.0
563 
564  theta(:,1,1) = current_state%zth%data(:, jcol, icol) + current_state%global_grid%configuration%vertical%thref(:)
565  dth(:,1,1) = current_state%sth%data(:, jcol, icol)
566  exner(:,1,1) = current_state%global_grid%configuration%vertical%rprefrcp(:)
567  pressure(:,1,1) = current_state%global_grid%configuration%vertical%prefn(:)
568  z_centre(:,1,1) = current_state%global_grid%configuration%vertical%zn(:)
569  dz(:,1,1) = current_state%global_grid%configuration%vertical%dz(:)
570  z_half(:kte-1,1,1) = current_state%global_grid%configuration%vertical%z(:)
571  rho(:,1,1) = current_state%global_grid%configuration%vertical%rhon(:)
572  w(:,1,1) = current_state%zw%data(:, jcol, icol)
573  tke(:,1,1) = 0.1 ! Test value
574 
575  iqx = iqv
576  qv(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
577  dqv(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
578 
579  ! Warm microphysical fields
580  IF (nq_l > 0)then
581  iqx = iql
582  qc(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
583  dqc(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
584  end IF
585  IF (nq_r > 0)then
586  iqx = iqr
587  qr(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
588  dqr(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
589  end IF
590  IF (nq_l > 1)then
591  iqx = inl
592  nc(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
593  dnc(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
594  end IF
595  IF (nq_r > 1)then
596  iqx = inr
597  nr(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
598  dnr(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
599  end IF
600  IF (nq_r > 2)then
601  iqx = i3mr
602  m3r(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
603  dm3r(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
604  end IF
605 
606  ! Ice microphysical fields
607  IF (nq_i > 0)then
608  iqx = iqi
609  qi(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
610  dqi(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
611  end IF
612  IF (nq_s > 0)then
613  iqx = iqs
614  qs(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
615  dqs(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
616  end IF
617  IF (nq_g > 0)then
618  iqx = iqg
619  qg(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
620  dqg(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
621  end IF
622  IF (nq_i > 1)then
623  iqx = ini
624  ni(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
625  dni(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
626  end IF
627  IF (nq_s > 1)then
628  iqx = ins
629  ns(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
630  dns(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
631  end IF
632  IF (nq_g > 1)then
633  iqx = ing
634  ng(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
635  dng(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
636  end IF
637  IF (nq_s > 2)then
638  iqx = i3ms
639  m3s(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
640  dm3s(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
641  end IF
642  IF (nq_g > 2)then
643  iqx = i3mg
644  m3g(:,1,1) = current_state%zq(iqx)%data(:,jcol,icol)
645  dm3g(:,1,1) = current_state%sq(iqx)%data(:,jcol,icol)
646  end IF
647 
648  ! Aerosol fields
649 
650  if (i_aitkensolmass>0) aitkensolmass(:,1,1) = current_state%zq(i_aitkensolmass)%data(:,jcol,icol)
651  if (i_aitkensolmass>0) daitkensolmass(:,1,1) = current_state%sq(i_aitkensolmass)%data(:,jcol,icol)
652  if (i_aitkensolnumber>0) aitkensolnumber(:,1,1) = current_state%zq(i_aitkensolnumber)%data(:,jcol,icol)
653  if (i_aitkensolnumber>0) daitkensolnumber(:,1,1) = current_state%sq(i_aitkensolnumber)%data(:,jcol,icol)
654  if (i_accumsolmass>0) accumsolmass(:,1,1) = current_state%zq(i_accumsolmass)%data(:,jcol,icol)
655  if (i_accumsolmass>0) daccumsolmass(:,1,1) = current_state%sq(i_accumsolmass)%data(:,jcol,icol)
656  if (i_accumsolnumber>0) accumsolnumber(:,1,1) = current_state%zq(i_accumsolnumber)%data(:,jcol,icol)
657  if (i_accumsolnumber>0) daccumsolnumber(:,1,1) = current_state%sq(i_accumsolnumber)%data(:,jcol,icol)
658  if (i_coarsesolmass>0) coarsesolmass(:,1,1) = current_state%zq(i_coarsesolmass)%data(:,jcol,icol)
659  if (i_coarsesolmass>0) dcoarsesolmass(:,1,1) = current_state%sq(i_coarsesolmass)%data(:,jcol,icol)
660  if (i_coarsesolnumber>0) coarsesolnumber(:,1,1) = current_state%zq(i_coarsesolnumber)%data(:,jcol,icol)
661  if (i_coarsesolnumber>0) dcoarsesolnumber(:,1,1) = current_state%sq(i_coarsesolnumber)%data(:,jcol,icol)
662  if (i_activesolliquid>0) activesolliquid(:,1,1) = current_state%zq(i_activesolliquid)%data(:,jcol,icol)
663  if (i_activesolliquid>0) dactivesolliquid(:,1,1) = current_state%sq(i_activesolliquid)%data(:,jcol,icol)
664  if (i_coarsedustmass>0) coarsedustmass(:,1,1) = current_state%zq(i_coarsedustmass)%data(:,jcol,icol)
665  if (i_coarsedustmass>0) dcoarsedustmass(:,1,1) = current_state%sq(i_coarsedustmass)%data(:,jcol,icol)
666  if (i_coarsedustnumber>0) coarsedustnumber(:,1,1) = current_state%zq(i_coarsedustnumber)%data(:,jcol,icol)
667  if (i_coarsedustnumber>0) dcoarsedustnumber(:,1,1) = current_state%sq(i_coarsedustnumber)%data(:,jcol,icol)
668  if (i_activeinsolice>0) activeinsolice(:,1,1) = current_state%zq(i_activeinsolice)%data(:,jcol,icol)
669  if (i_activeinsolice>0) dactiveinsolice(:,1,1) = current_state%sq(i_activeinsolice)%data(:,jcol,icol)
670  if (i_activesolice>0) activesolice(:,1,1) = current_state%zq(i_activesolice)%data(:,jcol,icol)
671  if (i_activesolice>0) dactivesolice(:,1,1) = current_state%sq(i_activesolice)%data(:,jcol,icol)
672  if (i_activeinsolliquid>0) activeinsolliquid(:,1,1) = current_state%zq(i_activeinsolliquid)%data(:,jcol,icol)
673  if (i_activeinsolliquid>0)dactiveinsolliquid(:,1,1) = current_state%sq(i_activeinsolliquid)%data(:,jcol,icol)
674  if (i_accuminsolmass>0) accuminsolmass(:,1,1) = current_state%zq(i_accuminsolmass)%data(:,jcol,icol)
675  if (i_accuminsolmass>0) daccuminsolmass(:,1,1) = current_state%sq(i_accuminsolmass)%data(:,jcol,icol)
676  if (i_accuminsolnumber>0) accuminsolnumber(:,1,1) = current_state%zq(i_accuminsolnumber)%data(:,jcol,icol)
677  if (i_accuminsolnumber>0) daccuminsolnumber(:,1,1) = current_state%sq(i_accuminsolnumber)%data(:,jcol,icol)
678  if (i_activesolnumber>0) activesolnumber(:,1,1) = current_state%zq(i_activesolnumber)%data(:,jcol,icol)
679  if (i_activesolnumber>0) dactivesolnumber(:,1,1) = current_state%sq(i_activesolnumber)%data(:,jcol,icol)
680  if (i_activeinsolnumber>0) activeinsolnumber(:,1,1) = current_state%zq(i_activeinsolnumber)%data(:,jcol,icol)
681  if (i_activeinsolnumber>0)dactiveinsolnumber(:,1,1) = current_state%sq(i_activeinsolnumber)%data(:,jcol,icol)
682 
683  CALL shipway_microphysics( &
684  ! in
685  its, ite, &
686  jts, jte, &
687  kts, kte, &
688  dtwp, &
689  qv, qc, qr, &
690  nc, nr, m3r, &
691  qi, qs, qg, &
692  ni, ns, ng, &
693  m3s, m3g, &
694  theta, &
695  aitkensolmass, aitkensolnumber, &
696  accumsolmass, accumsolnumber, &
697  coarsesolmass, coarsesolnumber, &
698  activesolliquid, &
699  activesolrain, &
700  coarsedustmass, coarsedustnumber, &
701  activeinsolice, &
702  activesolice, &
703  activeinsolliquid, &
704  accuminsolmass, &
705  accuminsolnumber, &
706  activesolnumber, &
707  activeinsolnumber, &
708  aitkensolbk, &
709  accumsolbk, &
710  coarsesolbk, &
711  exner, &
712  pressure, rho, &
713  w, tke, &
714  z_half, z_centre, &
715  dz, &
716  ! in/out
717  dqv, dqc, dqr, dnc, dnr, dm3r, &
718  dqi, dqs, dqg, dni, dns, dng, dm3s, dm3g, &
719  dth, &
720  daitkensolmass, daitkensolnumber, &
721  daccumsolmass, daccumsolnumber, &
722  dcoarsesolmass, dcoarsesolnumber, &
723  dactivesolliquid, &
724  dactivesolrain, &
725  dcoarsedustmass, dcoarsedustnumber, &
726  dactiveinsolice, &
727  dactivesolice, &
728  dactiveinsolliquid, &
729  daccuminsolmass, &
730  daccuminsolnumber, &
731  dactivesolnumber, &
732  dactiveinsolnumber, &
733  ils, ile, &
734  jls, jle, &
735  kls, kle, &
736  l_tendency=.true. &
737  )
738 
739  ! write back the tendencies
740  current_state%sth%data(:,jcol,icol) = current_state%sth%data(:,jcol,icol) + dth(:,1,1)
741 
742  iqx = iqv
743  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dqv(:,1,1)
744 
745  ! Warm microphysical fields
746  IF (nq_l > 0)then
747  iqx = iql
748  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dqc(:,1,1)
749  end IF
750 
751  IF (nq_r > 0)then
752  iqx = iqr
753  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dqr(:,1,1)
754  end IF
755  IF (nq_l > 1)then
756  iqx = inl
757  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dnc(:,1,1)
758  end IF
759  IF (nq_r > 1)then
760  iqx = inr
761  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dnr(:,1,1)
762  end IF
763  IF (nq_r > 2)then
764  iqx = i3mr
765  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dm3r(:,1,1)
766  end IF
767 
768  ! Ice microphysical fields
769  IF (nq_i > 0)then
770  iqx = iqi
771  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dqi(:,1,1)
772  end IF
773  IF (nq_s > 0)then
774  iqx = iqs
775  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dqs(:,1,1)
776  end IF
777  IF (nq_g > 0)then
778  iqx = iqg
779  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dqg(:,1,1)
780  end IF
781  IF (nq_i > 1)then
782  iqx = ini
783  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dni(:,1,1)
784  end IF
785  IF (nq_s > 1)then
786  iqx = ins
787  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dns(:,1,1)
788  end IF
789  IF (nq_g > 1)then
790  iqx = ing
791  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dng(:,1,1)
792  end IF
793  IF (nq_s > 2)then
794  iqx = i3ms
795  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dm3s(:,1,1)
796  end IF
797  IF (nq_g > 2)then
798  iqx = i3mg
799  current_state%sq(iqx)%data(:,jcol,icol) = current_state%sq(iqx)%data(:,jcol,icol) + dm3g(:,1,1)
800  end IF
801 
802  ! Aerosol fields
803 
804  if (i_aitkensolmass>0) current_state%sq(i_aitkensolmass)%data(:,jcol,icol) &
805  = current_state%sq(i_aitkensolmass)%data(:,jcol,icol) + daitkensolmass(:,1,1)
806  if (i_aitkensolnumber>0) current_state%sq(i_aitkensolnumber)%data(:,jcol,icol) &
807  = current_state%sq(i_aitkensolnumber)%data(:,jcol,icol) + daitkensolnumber(:,1,1)
808  if (i_accumsolmass>0) current_state%sq(i_accumsolmass)%data(:,jcol,icol) &
809  = current_state%sq(i_accumsolmass)%data(:,jcol,icol) + daccumsolmass(:,1,1)
810  if (i_accumsolnumber>0) current_state%sq(i_accumsolnumber)%data(:,jcol,icol) &
811  = current_state%sq(i_accumsolnumber)%data(:,jcol,icol) + daccumsolnumber(:,1,1)
812  if (i_coarsesolmass>0) current_state%sq(i_coarsesolmass)%data(:,jcol,icol) &
813  = current_state%sq(i_coarsesolmass)%data(:,jcol,icol) + dcoarsesolmass(:,1,1)
814  if (i_coarsesolnumber>0) current_state%sq(i_coarsesolnumber)%data(:,jcol,icol) &
815  = current_state%sq(i_coarsesolnumber)%data(:,jcol,icol) + dcoarsesolnumber(:,1,1)
816  if (i_activesolliquid>0) current_state%sq(i_activesolliquid)%data(:,jcol,icol) &
817  = current_state%sq(i_activesolliquid)%data(:,jcol,icol) + dactivesolliquid(:,1,1)
818  if (i_coarsedustmass>0) current_state%sq(i_coarsedustmass)%data(:,jcol,icol) &
819  = current_state%sq(i_coarsedustmass)%data(:,jcol,icol) + dcoarsedustmass(:,1,1)
820  if (i_coarsedustnumber>0) current_state%sq(i_coarsedustnumber)%data(:,jcol,icol) &
821  = current_state%sq(i_coarsedustnumber)%data(:,jcol,icol) + dcoarsedustnumber(:,1,1)
822  if (i_activeinsolice>0) current_state%sq(i_activeinsolice)%data(:,jcol,icol) &
823  = current_state%sq(i_activeinsolice)%data(:,jcol,icol) + dactiveinsolice(:,1,1)
824  if (i_activesolice>0) current_state%sq(i_activesolice)%data(:,jcol,icol) &
825  = current_state%sq(i_activesolice)%data(:,jcol,icol) + dactivesolice(:,1,1)
826  if (i_activeinsolliquid>0) current_state%sq(i_activeinsolliquid)%data(:,jcol,icol) &
827  = current_state%sq(i_activeinsolliquid)%data(:,jcol,icol) + dactiveinsolliquid(:,1,1)
828  if (i_accuminsolmass>0) current_state%sq(i_accuminsolmass)%data(:,jcol,icol) &
829  = current_state%sq(i_accuminsolmass)%data(:,jcol,icol) + daccuminsolmass(:,1,1)
830  if (i_accuminsolnumber>0) current_state%sq(i_accuminsolnumber)%data(:,jcol,icol) &
831  = current_state%sq(i_accuminsolnumber)%data(:,jcol,icol) + daccuminsolnumber(:,1,1)
832  if (i_activesolnumber>0) current_state%sq(i_activesolnumber)%data(:,jcol,icol) &
833  = current_state%sq(i_activesolnumber)%data(:,jcol,icol) + dactivesolnumber(:,1,1)
834  if (i_activeinsolnumber>0) current_state%sq(i_activeinsolnumber)%data(:,jcol,icol) &
835  = current_state%sq(i_activeinsolnumber)%data(:,jcol,icol) + dactiveinsolnumber(:,1,1)
836 
837  ! for total surface precipitation, sum the surface rain rate (cloud + rain which is precip_r)
838  ! and surface
839  ! snow rate (precip_s), which is the sum of ice, snow and graupel (See micromain.F90 in casim for
840  ! calculation).
841  if (l_warm) then
842  surface_precip(target_y_index,target_x_index) = &
843  casdiags % SurfaceRainR(1,1)
844  else
845  surface_precip(target_y_index,target_x_index) = &
846  casdiags % SurfaceRainR(1,1) + casdiags % SurfaceSnowR(1,1)
847  endif
848  call populate_casim_monc_dg(current_state, casdiags)
849 
850 
Here is the caller graph for this function:

Variable Documentation

◆ accuminsolmass

real(wp), dimension(:,:,:), allocatable casim_mod::accuminsolmass
private

Definition at line 107 of file casim.F90.

107  REAL(wp), allocatable :: AccumInsolMass(:,:,:) ! Accum mode dust mass

◆ accuminsolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::accuminsolnumber
private

Definition at line 108 of file casim.F90.

108  REAL(wp), allocatable :: AccumInsolNumber(:,:,:) ! Accum mode dust number

◆ accumsolbk

real(wp), dimension(:,:,:), allocatable casim_mod::accumsolbk
private

Definition at line 116 of file casim.F90.

116  REAL(wp), allocatable :: AccumSolBk(:,:,:)

◆ accumsolmass

real(wp), dimension(:,:,:), allocatable casim_mod::accumsolmass
private

Definition at line 98 of file casim.F90.

98  REAL(wp), allocatable :: AccumSolMass(:,:,:), AccumSolNumber(:,:,:) ! Accumulation mode aerosol

◆ accumsolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::accumsolnumber
private

Definition at line 98 of file casim.F90.

◆ activeinsolice

real(wp), dimension(:,:,:), allocatable casim_mod::activeinsolice
private

Definition at line 104 of file casim.F90.

104  REAL(wp), allocatable :: ActiveInsolIce(:,:,:) ! Activeated dust

◆ activeinsolliquid

real(wp), dimension(:,:,:), allocatable casim_mod::activeinsolliquid
private

Definition at line 106 of file casim.F90.

106  REAL(wp), allocatable :: ActiveInsolLiquid(:,:,:) ! Activeated dust in cloud

◆ activeinsolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::activeinsolnumber
private

Definition at line 110 of file casim.F90.

110  REAL(wp), allocatable :: ActiveInsolNumber(:,:,:) ! Activated insoluble number (if we need a tracer)

◆ activesolice

real(wp), dimension(:,:,:), allocatable casim_mod::activesolice
private

Definition at line 105 of file casim.F90.

105  REAL(wp), allocatable :: ActiveSolIce(:,:,:) ! Activeated aerosol in ice

◆ activesolliquid

real(wp), dimension(:,:,:), allocatable casim_mod::activesolliquid
private

Definition at line 99 of file casim.F90.

99  REAL(wp), allocatable :: ActiveSolLiquid(:,:,:) ! Activated aerosol

◆ activesolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::activesolnumber
private

Definition at line 109 of file casim.F90.

109  REAL(wp), allocatable :: ActiveSolNumber(:,:,:) ! Activated soluble number (if we need a tracer)

◆ activesolrain

real(wp), dimension(:,:,:), allocatable casim_mod::activesolrain
private

Definition at line 102 of file casim.F90.

102  REAL(wp), allocatable :: ActiveSolRain(:,:,:) ! Activeated aerosol in rain

◆ aitkensolbk

real(wp), dimension(:,:,:), allocatable casim_mod::aitkensolbk
private

Definition at line 115 of file casim.F90.

115  REAL(wp), allocatable :: AitkenSolBk(:,:,:)

◆ aitkensolmass

real(wp), dimension(:,:,:), allocatable casim_mod::aitkensolmass
private

Definition at line 100 of file casim.F90.

100  REAL(wp), allocatable :: AitkenSolMass(:,:,:), AitkenSolNumber(:,:,:) ! Aitken mode aerosol

◆ aitkensolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::aitkensolnumber
private

Definition at line 100 of file casim.F90.

◆ coarsedustmass

real(wp), dimension(:,:,:), allocatable casim_mod::coarsedustmass
private

Definition at line 103 of file casim.F90.

103  REAL(wp), allocatable :: CoarseDustMass(:,:,:), CoarseDustNumber(:,:,:) ! Coarse Dust

◆ coarsedustnumber

real(wp), dimension(:,:,:), allocatable casim_mod::coarsedustnumber
private

Definition at line 103 of file casim.F90.

◆ coarsesolbk

real(wp), dimension(:,:,:), allocatable casim_mod::coarsesolbk
private

Definition at line 117 of file casim.F90.

117  REAL(wp), allocatable :: CoarseSolBk(:,:,:)

◆ coarsesolmass

real(wp), dimension(:,:,:), allocatable casim_mod::coarsesolmass
private

Definition at line 101 of file casim.F90.

101  REAL(wp), allocatable :: CoarseSolMass(:,:,:), CoarseSolNumber(:,:,:) ! Course mode aerosol

◆ coarsesolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::coarsesolnumber
private

Definition at line 101 of file casim.F90.

◆ daccuminsolmass

real(wp), dimension(:,:,:), allocatable casim_mod::daccuminsolmass
private

Definition at line 135 of file casim.F90.

135  REAL(wp), allocatable :: dAccumInsolMass(:,:,:) ! Accum mode dust mass

◆ daccuminsolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::daccuminsolnumber
private

Definition at line 136 of file casim.F90.

136  REAL(wp), allocatable :: dAccumInsolNumber(:,:,:) ! Accum mode dust number

◆ daccumsolmass

real(wp), dimension(:,:,:), allocatable casim_mod::daccumsolmass
private

Definition at line 126 of file casim.F90.

126  REAL(wp), allocatable :: dAccumSolMass(:,:,:), dAccumSolNumber(:,:,:) ! Accumulation mode aerosol

◆ daccumsolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::daccumsolnumber
private

Definition at line 126 of file casim.F90.

◆ dactiveinsolice

real(wp), dimension(:,:,:), allocatable casim_mod::dactiveinsolice
private

Definition at line 132 of file casim.F90.

132  REAL(wp), allocatable :: dActiveInsolIce(:,:,:) ! Activeated dust

◆ dactiveinsolliquid

real(wp), dimension(:,:,:), allocatable casim_mod::dactiveinsolliquid
private

Definition at line 134 of file casim.F90.

134  REAL(wp), allocatable :: dActiveInsolLiquid(:,:,:) ! Activeated dust in cloud

◆ dactiveinsolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::dactiveinsolnumber
private

Definition at line 138 of file casim.F90.

138  REAL(wp), allocatable :: dActiveInsolNumber(:,:,:) ! Activated insoluble number (if we need a tracer)

◆ dactivesolice

real(wp), dimension(:,:,:), allocatable casim_mod::dactivesolice
private

Definition at line 133 of file casim.F90.

133  REAL(wp), allocatable :: dActiveSolIce(:,:,:) ! Activeated aerosol in ice

◆ dactivesolliquid

real(wp), dimension(:,:,:), allocatable casim_mod::dactivesolliquid
private

Definition at line 127 of file casim.F90.

127  REAL(wp), allocatable :: dActiveSolLiquid(:,:,:) ! Activated aerosol

◆ dactivesolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::dactivesolnumber
private

Definition at line 137 of file casim.F90.

137  REAL(wp), allocatable :: dActiveSolNumber(:,:,:) ! Activated soluble number (if we need a tracer)

◆ dactivesolrain

real(wp), dimension(:,:,:), allocatable casim_mod::dactivesolrain
private

Definition at line 130 of file casim.F90.

130  REAL(wp), allocatable :: dActiveSolRain(:,:,:) ! Activeated aerosol in rain

◆ daitkensolmass

real(wp), dimension(:,:,:), allocatable casim_mod::daitkensolmass
private

Definition at line 128 of file casim.F90.

128  REAL(wp), allocatable :: dAitkenSolMass(:,:,:), dAitkenSolNumber(:,:,:) ! Aitken mode aerosol

◆ daitkensolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::daitkensolnumber
private

Definition at line 128 of file casim.F90.

◆ dcoarsedustmass

real(wp), dimension(:,:,:), allocatable casim_mod::dcoarsedustmass
private

Definition at line 131 of file casim.F90.

131  REAL(wp), allocatable :: dCoarseDustMass(:,:,:), dCoarseDustNumber(:,:,:) ! Dust

◆ dcoarsedustnumber

real(wp), dimension(:,:,:), allocatable casim_mod::dcoarsedustnumber
private

Definition at line 131 of file casim.F90.

◆ dcoarsesolmass

real(wp), dimension(:,:,:), allocatable casim_mod::dcoarsesolmass
private

Definition at line 129 of file casim.F90.

129  REAL(wp), allocatable :: dCoarseSolMass(:,:,:), dCoarseSolNumber(:,:,:) ! Course mode aerosol

◆ dcoarsesolnumber

real(wp), dimension(:,:,:), allocatable casim_mod::dcoarsesolnumber
private

Definition at line 129 of file casim.F90.

◆ dm3g

real(wp), dimension(:,:,:), allocatable casim_mod::dm3g
private

Definition at line 121 of file casim.F90.

◆ dm3r

real(wp), dimension(:,:,:), allocatable casim_mod::dm3r
private

Definition at line 121 of file casim.F90.

◆ dm3s

real(wp), dimension(:,:,:), allocatable casim_mod::dm3s
private

Definition at line 121 of file casim.F90.

◆ dnc

real(wp), dimension(:,:,:), allocatable casim_mod::dnc
private

Definition at line 121 of file casim.F90.

◆ dng

real(wp), dimension(:,:,:), allocatable casim_mod::dng
private

Definition at line 121 of file casim.F90.

◆ dni

real(wp), dimension(:,:,:), allocatable casim_mod::dni
private

Definition at line 121 of file casim.F90.

◆ dnr

real(wp), dimension(:,:,:), allocatable casim_mod::dnr
private

Definition at line 121 of file casim.F90.

◆ dns

real(wp), dimension(:,:,:), allocatable casim_mod::dns
private

Definition at line 121 of file casim.F90.

◆ dqc

real(wp), dimension(:,:,:), allocatable casim_mod::dqc
private

Definition at line 121 of file casim.F90.

◆ dqg

real(wp), dimension(:,:,:), allocatable casim_mod::dqg
private

Definition at line 121 of file casim.F90.

◆ dqi

real(wp), dimension(:,:,:), allocatable casim_mod::dqi
private

Definition at line 121 of file casim.F90.

◆ dqr

real(wp), dimension(:,:,:), allocatable casim_mod::dqr
private

Definition at line 121 of file casim.F90.

◆ dqs

real(wp), dimension(:,:,:), allocatable casim_mod::dqs
private

Definition at line 121 of file casim.F90.

◆ dqv

real(wp), dimension(:,:,:), allocatable casim_mod::dqv
private

Definition at line 121 of file casim.F90.

121  REAL(wp), allocatable :: dqv(:,:,:), dth(:,:,:), dqc(:,:,:), dnc(:,:,:) &
122  , dqr(:,:,:), dnr(:,:,:), dm3r(:,:,:) &
123  , dqi(:,:,:), dni(:,:,:), dqs(:,:,:), dns(:,:,:), dm3s(:,:,:) &
124  , dqg(:,:,:), dng(:,:,:), dm3g(:,:,:)

◆ dth

real(wp), dimension(:,:,:), allocatable casim_mod::dth
private

Definition at line 121 of file casim.F90.

◆ dz

real(wp), dimension(:,:,:), allocatable casim_mod::dz
private

Definition at line 91 of file casim.F90.

◆ exner

real(wp), dimension(:,:,:), allocatable casim_mod::exner
private

Definition at line 91 of file casim.F90.

◆ i3mg

integer casim_mod::i3mg =0
private

Definition at line 147 of file casim.F90.

◆ i3mr

integer casim_mod::i3mr =0
private

Definition at line 147 of file casim.F90.

147  INTEGER :: i3mr=0, i3ms=0, i3mg=0

◆ i3ms

integer casim_mod::i3ms =0
private

Definition at line 147 of file casim.F90.

◆ i_accuminsolmass

integer casim_mod::i_accuminsolmass =0
private

Definition at line 148 of file casim.F90.

◆ i_accuminsolnumber

integer casim_mod::i_accuminsolnumber =0
private

Definition at line 148 of file casim.F90.

◆ i_accumsolmass

integer casim_mod::i_accumsolmass =0
private

Definition at line 148 of file casim.F90.

148  INTEGER :: &
149  i_AccumSolMass=0, &
150  i_accumsolnumber=0, &
151  i_activesolliquid=0, &
152  i_aitkensolmass=0, &
153  i_aitkensolnumber=0, &
154  i_coarsesolmass=0, &
155  i_coarsesolnumber=0, &
156  i_activesolrain=0, &
157  i_coarsedustmass=0, &
158  i_coarsedustnumber=0, &
159  i_activeinsolice=0, &
160  i_activesolice=0, &
161  i_activeinsolliquid=0, &
162  i_accuminsolmass=0, &
163  i_accuminsolnumber=0, &
164  i_activesolnumber=0, &
165  i_activeinsolnumber=0

◆ i_accumsolnumber

integer casim_mod::i_accumsolnumber =0
private

Definition at line 148 of file casim.F90.

◆ i_activeinsolice

integer casim_mod::i_activeinsolice =0
private

Definition at line 148 of file casim.F90.

◆ i_activeinsolliquid

integer casim_mod::i_activeinsolliquid =0
private

Definition at line 148 of file casim.F90.

◆ i_activeinsolnumber

integer casim_mod::i_activeinsolnumber =0
private

Definition at line 148 of file casim.F90.

◆ i_activesolice

integer casim_mod::i_activesolice =0
private

Definition at line 148 of file casim.F90.

◆ i_activesolliquid

integer casim_mod::i_activesolliquid =0
private

Definition at line 148 of file casim.F90.

◆ i_activesolnumber

integer casim_mod::i_activesolnumber =0
private

Definition at line 148 of file casim.F90.

◆ i_activesolrain

integer casim_mod::i_activesolrain =0
private

Definition at line 148 of file casim.F90.

◆ i_aitkensolmass

integer casim_mod::i_aitkensolmass =0
private

Definition at line 148 of file casim.F90.

◆ i_aitkensolnumber

integer casim_mod::i_aitkensolnumber =0
private

Definition at line 148 of file casim.F90.

◆ i_coarsedustmass

integer casim_mod::i_coarsedustmass =0
private

Definition at line 148 of file casim.F90.

◆ i_coarsedustnumber

integer casim_mod::i_coarsedustnumber =0
private

Definition at line 148 of file casim.F90.

◆ i_coarsesolmass

integer casim_mod::i_coarsesolmass =0
private

Definition at line 148 of file casim.F90.

◆ i_coarsesolnumber

integer casim_mod::i_coarsesolnumber =0
private

Definition at line 148 of file casim.F90.

◆ ile

integer casim_mod::ile
private

Definition at line 142 of file casim.F90.

◆ ils

integer casim_mod::ils
private

Definition at line 142 of file casim.F90.

142  INTEGER :: ils,ile, jls,jle, kls,kle, &
143  its,ite, jts,jte, kts,kte

◆ ing

integer casim_mod::ing =0
private

Definition at line 146 of file casim.F90.

◆ ini

integer casim_mod::ini =0
private

Definition at line 146 of file casim.F90.

◆ inl

integer casim_mod::inl =0
private

Definition at line 146 of file casim.F90.

146  INTEGER :: inl=0, inr=0, ini=0, ins=0, ing=0

◆ inr

integer casim_mod::inr =0
private

Definition at line 146 of file casim.F90.

◆ ins

integer casim_mod::ins =0
private

Definition at line 146 of file casim.F90.

◆ iqg

integer casim_mod::iqg =0
private

Definition at line 145 of file casim.F90.

◆ iqi

integer casim_mod::iqi =0
private

Definition at line 145 of file casim.F90.

◆ iql

integer casim_mod::iql =0
private

Definition at line 145 of file casim.F90.

◆ iqr

integer casim_mod::iqr =0
private

Definition at line 145 of file casim.F90.

◆ iqs

integer casim_mod::iqs =0
private

Definition at line 145 of file casim.F90.

◆ iqv

integer casim_mod::iqv =0
private

Definition at line 145 of file casim.F90.

145  INTEGER :: iqv=0, iql=0, iqr=0, iqi=0, iqs=0, iqg=0

◆ ite

integer casim_mod::ite
private

Definition at line 142 of file casim.F90.

◆ its

integer casim_mod::its
private

Definition at line 142 of file casim.F90.

◆ jle

integer casim_mod::jle
private

Definition at line 142 of file casim.F90.

◆ jls

integer casim_mod::jls
private

Definition at line 142 of file casim.F90.

◆ jte

integer casim_mod::jte
private

Definition at line 142 of file casim.F90.

◆ jts

integer casim_mod::jts
private

Definition at line 142 of file casim.F90.

◆ kle

integer casim_mod::kle
private

Definition at line 142 of file casim.F90.

◆ kls

integer casim_mod::kls
private

Definition at line 142 of file casim.F90.

◆ kte

integer casim_mod::kte
private

Definition at line 142 of file casim.F90.

◆ kts

integer casim_mod::kts
private

Definition at line 142 of file casim.F90.

◆ m3g

real(wp), dimension(:,:,:), allocatable casim_mod::m3g
private

Definition at line 91 of file casim.F90.

◆ m3r

real(wp), dimension(:,:,:), allocatable casim_mod::m3r
private

Definition at line 91 of file casim.F90.

◆ m3s

real(wp), dimension(:,:,:), allocatable casim_mod::m3s
private

Definition at line 91 of file casim.F90.

◆ nc

real(wp), dimension(:,:,:), allocatable casim_mod::nc
private

Definition at line 91 of file casim.F90.

◆ ng

real(wp), dimension(:,:,:), allocatable casim_mod::ng
private

Definition at line 91 of file casim.F90.

◆ ni

real(wp), dimension(:,:,:), allocatable casim_mod::ni
private

Definition at line 91 of file casim.F90.

◆ nr

real(wp), dimension(:,:,:), allocatable casim_mod::nr
private

Definition at line 91 of file casim.F90.

◆ ns

real(wp), dimension(:,:,:), allocatable casim_mod::ns
private

Definition at line 91 of file casim.F90.

◆ pcond_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pcond_tot
private

Definition at line 167 of file casim.F90.

◆ pgacs_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pgacs_tot
private

Definition at line 167 of file casim.F90.

◆ pgacw_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pgacw_tot
private

Definition at line 167 of file casim.F90.

◆ pgmlt_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pgmlt_tot
private

Definition at line 167 of file casim.F90.

◆ pgsub_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pgsub_tot
private

Definition at line 167 of file casim.F90.

◆ phomc_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::phomc_tot
private

Definition at line 167 of file casim.F90.

167  real(kind=default_precision), dimension(:), allocatable :: &
168  phomc_tot, pinuc_tot, pidep_tot, psdep_tot, piacw_tot, psacw_tot, psacr_tot, pisub_tot, &
169  pssub_tot, pimlt_tot, psmlt_tot, psaut_tot, psaci_tot, praut_tot, pracw_tot, prevp_tot, &
170  pgacw_tot, pgacs_tot, pgmlt_tot, pgsub_tot, psedi_tot, pseds_tot, psedr_tot, psedg_tot, &
171  psedl_tot, pcond_tot

◆ piacw_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::piacw_tot
private

Definition at line 167 of file casim.F90.

◆ pidep_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pidep_tot
private

Definition at line 167 of file casim.F90.

◆ pimlt_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pimlt_tot
private

Definition at line 167 of file casim.F90.

◆ pinuc_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pinuc_tot
private

Definition at line 167 of file casim.F90.

◆ pisub_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pisub_tot
private

Definition at line 167 of file casim.F90.

◆ pracw_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pracw_tot
private

Definition at line 167 of file casim.F90.

◆ praut_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::praut_tot
private

Definition at line 167 of file casim.F90.

◆ pressure

real(wp), dimension(:,:,:), allocatable casim_mod::pressure
private

Definition at line 91 of file casim.F90.

◆ prevp_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::prevp_tot
private

Definition at line 167 of file casim.F90.

◆ psaci_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psaci_tot
private

Definition at line 167 of file casim.F90.

◆ psacr_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psacr_tot
private

Definition at line 167 of file casim.F90.

◆ psacw_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psacw_tot
private

Definition at line 167 of file casim.F90.

◆ psaut_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psaut_tot
private

Definition at line 167 of file casim.F90.

◆ psdep_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psdep_tot
private

Definition at line 167 of file casim.F90.

◆ psedg_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psedg_tot
private

Definition at line 167 of file casim.F90.

◆ psedi_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psedi_tot
private

Definition at line 167 of file casim.F90.

◆ psedl_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psedl_tot
private

Definition at line 167 of file casim.F90.

◆ psedr_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psedr_tot
private

Definition at line 167 of file casim.F90.

◆ pseds_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pseds_tot
private

Definition at line 167 of file casim.F90.

◆ psmlt_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::psmlt_tot
private

Definition at line 167 of file casim.F90.

◆ pssub_tot

real(kind=default_precision), dimension(:), allocatable casim_mod::pssub_tot
private

Definition at line 167 of file casim.F90.

◆ qc

real(wp), dimension(:,:,:), allocatable casim_mod::qc
private

Definition at line 91 of file casim.F90.

◆ qg

real(wp), dimension(:,:,:), allocatable casim_mod::qg
private

Definition at line 91 of file casim.F90.

◆ qi

real(wp), dimension(:,:,:), allocatable casim_mod::qi
private

Definition at line 91 of file casim.F90.

◆ qr

real(wp), dimension(:,:,:), allocatable casim_mod::qr
private

Definition at line 91 of file casim.F90.

◆ qs

real(wp), dimension(:,:,:), allocatable casim_mod::qs
private

Definition at line 91 of file casim.F90.

◆ qv

real(wp), dimension(:,:,:), allocatable casim_mod::qv
private

Definition at line 91 of file casim.F90.

◆ rho

real(wp), dimension(:,:,:), allocatable casim_mod::rho
private

Definition at line 91 of file casim.F90.

◆ surface_precip

real(wp), dimension(:,:), allocatable casim_mod::surface_precip
private

Definition at line 140 of file casim.F90.

140  REAL(wp), allocatable :: surface_precip(:,:)

◆ theta

real(wp), dimension(:,:,:), allocatable casim_mod::theta
private

Definition at line 91 of file casim.F90.

91  REAL(wp), allocatable :: theta(:,:,:), pressure(:,:,:), &
92  z_half(:,:,:), z_centre(:,:,:), dz(:,:,:), qv(:,:,:),qc(:,:,:) &
93  , nc(:,:,:), qr(:,:,:), nr(:,:,:), m3r(:,:,:),rho(:,:,:) &
94  , exner(:,:,:), w(:,:,:), tke(:,:,:) &
95  , qi(:,:,:), ni(:,:,:), qs(:,:,:), ns(:,:,:), m3s(:,:,:) &
96  , qg(:,:,:), ng(:,:,:), m3g(:,:,:)

◆ tke

real(wp), dimension(:,:,:), allocatable casim_mod::tke
private

Definition at line 91 of file casim.F90.

◆ w

real(wp), dimension(:,:,:), allocatable casim_mod::w
private

Definition at line 91 of file casim.F90.

◆ z_centre

real(wp), dimension(:,:,:), allocatable casim_mod::z_centre
private

Definition at line 91 of file casim.F90.

◆ z_half

real(wp), dimension(:,:,:), allocatable casim_mod::z_half
private

Definition at line 91 of file casim.F90.

logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
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