MONC
casim_profile_dgs.F90
Go to the documentation of this file.
4  use grids_mod, only : z_index, y_index, x_index
7  use state_mod, only : model_state_type
9 
10  ! needs casim modules
11  use mphys_switches, only: l_warm
12  ! need casdiags for the diag switches
13  use generic_diagnostic_variables, ONLY: casdiags
14  ! and casim component structure, which contains the process rate data
16 
17  implicit none
18 
19 #ifndef TEST_MODE
20  private
21 #endif
22 
23  integer :: total_points, iqv, iql
24  real(kind=default_precision), dimension(:), allocatable :: &
25  ! local process rate totals
30  ! local total tendencies
33 
35 
36 contains
37 
41  casim_profile_dgs_get_descriptor%name="casim_profile_dgs"
43 
46 
49 
50  allocate(casim_profile_dgs_get_descriptor%published_fields(35))
51 
52  casim_profile_dgs_get_descriptor%published_fields(1)="phomc_total"
53  casim_profile_dgs_get_descriptor%published_fields(2)="pinuc_total"
54  casim_profile_dgs_get_descriptor%published_fields(3)="pidep_total"
55  casim_profile_dgs_get_descriptor%published_fields(4)="psdep_total"
56  casim_profile_dgs_get_descriptor%published_fields(5)="piacw_total"
57  casim_profile_dgs_get_descriptor%published_fields(6)="psacw_total"
58  casim_profile_dgs_get_descriptor%published_fields(7)="psacr_total"
59  casim_profile_dgs_get_descriptor%published_fields(8)="pisub_total"
60  casim_profile_dgs_get_descriptor%published_fields(9)="pssub_total"
61  casim_profile_dgs_get_descriptor%published_fields(10)="pimlt_total"
62  casim_profile_dgs_get_descriptor%published_fields(11)="psmlt_total"
63  casim_profile_dgs_get_descriptor%published_fields(12)="psaut_total"
64  casim_profile_dgs_get_descriptor%published_fields(13)="psaci_total"
65  casim_profile_dgs_get_descriptor%published_fields(14)="praut_total"
66  casim_profile_dgs_get_descriptor%published_fields(15)="pracw_total"
67  casim_profile_dgs_get_descriptor%published_fields(16)="prevp_total"
68  casim_profile_dgs_get_descriptor%published_fields(17)="pgacw_total"
69  casim_profile_dgs_get_descriptor%published_fields(18)="pgacs_total"
70  casim_profile_dgs_get_descriptor%published_fields(19)="pgmlt_total"
71  casim_profile_dgs_get_descriptor%published_fields(20)="pgsub_total"
72  casim_profile_dgs_get_descriptor%published_fields(21)="psedi_total"
73  casim_profile_dgs_get_descriptor%published_fields(22)="pseds_total"
74  casim_profile_dgs_get_descriptor%published_fields(23)="psedr_total"
75  casim_profile_dgs_get_descriptor%published_fields(24)="psedg_total"
76  casim_profile_dgs_get_descriptor%published_fields(25)="psedl_total"
77  casim_profile_dgs_get_descriptor%published_fields(26)="pcond_total"
78  casim_profile_dgs_get_descriptor%published_fields(27)="dth_mphys_total"
79  casim_profile_dgs_get_descriptor%published_fields(28)="dth_cond_evap_total"
80  casim_profile_dgs_get_descriptor%published_fields(29)="dqv_mphys_total"
81  casim_profile_dgs_get_descriptor%published_fields(30)="dqv_cond_evap_total"
82  casim_profile_dgs_get_descriptor%published_fields(31)="dqc_mphys_total"
83  casim_profile_dgs_get_descriptor%published_fields(32)="dqr_mphys_total"
84  casim_profile_dgs_get_descriptor%published_fields(33)="dqi_mphys_total"
85  casim_profile_dgs_get_descriptor%published_fields(34)="dqs_mphys_total"
86  casim_profile_dgs_get_descriptor%published_fields(35)="dqg_mphys_total"
87 
89 
90  subroutine initialisation_callback(current_state)
91  type(model_state_type), target, intent(inout) :: current_state
92 
93  integer :: k
94 
95  if (.not. is_component_enabled(current_state%options_database, "casim")) then
96  call log_master_log(log_error, "Casim profile diags requested but casim not enabled - check config, STOP")
97  end if
98 
99  ! allocate local arrays for the horizontal wind averages
100  allocate(psedl_tot(current_state%local_grid%size(z_index)), &
101  pcond_tot(current_state%local_grid%size(z_index)), &
102  praut_tot(current_state%local_grid%size(z_index)), &
103  pracw_tot(current_state%local_grid%size(z_index)), &
104  prevp_tot(current_state%local_grid%size(z_index)), &
105  psedr_tot(current_state%local_grid%size(z_index)), &
106  dth_mphys_tot(current_state%local_grid%size(z_index)), &
107  dth_cond_evap_tot(current_state%local_grid%size(z_index)), &
108  dqv_mphys_tot(current_state%local_grid%size(z_index)), &
109  dqv_cond_evap_tot(current_state%local_grid%size(z_index)), &
110  dqc_mphys_tot(current_state%local_grid%size(z_index)), &
111  dqr_mphys_tot(current_state%local_grid%size(z_index)))
112  if (.not. l_warm) then
113  allocate(phomc_tot(current_state%local_grid%size(z_index)), &
114  pinuc_tot(current_state%local_grid%size(z_index)), &
115  pidep_tot(current_state%local_grid%size(z_index)), &
116  piacw_tot(current_state%local_grid%size(z_index)), &
117  pisub_tot(current_state%local_grid%size(z_index)), &
118  pimlt_tot(current_state%local_grid%size(z_index)), &
119  psedi_tot(current_state%local_grid%size(z_index)), &
120  psacw_tot(current_state%local_grid%size(z_index)), &
121  psacr_tot(current_state%local_grid%size(z_index)), &
122  pssub_tot(current_state%local_grid%size(z_index)), &
123  psmlt_tot(current_state%local_grid%size(z_index)), &
124  psaut_tot(current_state%local_grid%size(z_index)), &
125  psaci_tot(current_state%local_grid%size(z_index)), &
126  psdep_tot(current_state%local_grid%size(z_index)), &
127  pseds_tot(current_state%local_grid%size(z_index)), &
128  pgacw_tot(current_state%local_grid%size(z_index)), &
129  pgacs_tot(current_state%local_grid%size(z_index)), &
130  pgmlt_tot(current_state%local_grid%size(z_index)), &
131  pgsub_tot(current_state%local_grid%size(z_index)), &
132  psedg_tot(current_state%local_grid%size(z_index)), &
133  dqi_mphys_tot(current_state%local_grid%size(z_index)), &
134  dqs_mphys_tot(current_state%local_grid%size(z_index)), &
135  dqg_mphys_tot(current_state%local_grid%size(z_index)))
136  endif
137 
138  end subroutine initialisation_callback
139 
140  subroutine timestep_callback(current_state)
141  type(model_state_type), target, intent(inout) :: current_state
142 
143  integer :: k, i
144  integer :: icol, jcol, target_x_index, target_y_index
145 
146  icol=current_state%column_local_x
147  jcol=current_state%column_local_y
148  target_y_index=jcol-current_state%local_grid%halo_size(y_index)
149  target_x_index=icol-current_state%local_grid%halo_size(x_index)
150 
151  if (current_state%first_timestep_column) then
152  psedl_tot(:)= 0.0_default_precision
153  pcond_tot(:)= 0.0_default_precision
154  praut_tot(:)= 0.0_default_precision
155  pracw_tot(:)= 0.0_default_precision
156  prevp_tot(:)= 0.0_default_precision
157  psedr_tot(:)= 0.0_default_precision
158  dth_mphys_tot(:)= 0.0_default_precision
159  dth_cond_evap_tot(:)= 0.0_default_precision
160  dqv_mphys_tot(:)= 0.0_default_precision
161  dqv_cond_evap_tot(:)= 0.0_default_precision
162  dqc_mphys_tot(:)= 0.0_default_precision
163  dqr_mphys_tot(:)= 0.0_default_precision
164  if (.not. l_warm) then
165  phomc_tot(:)= 0.0_default_precision
166  pinuc_tot(:)= 0.0_default_precision
167  pidep_tot(:)= 0.0_default_precision
168  piacw_tot(:)= 0.0_default_precision
169  pisub_tot(:)= 0.0_default_precision
170  pimlt_tot(:)= 0.0_default_precision
171  psedi_tot(:)= 0.0_default_precision
172  psacw_tot(:)= 0.0_default_precision
173  psacr_tot(:)= 0.0_default_precision
174  pssub_tot(:)= 0.0_default_precision
175  psmlt_tot(:)= 0.0_default_precision
176  psaut_tot(:)= 0.0_default_precision
177  psaci_tot(:)= 0.0_default_precision
178  psdep_tot(:)= 0.0_default_precision
179  pseds_tot(:)= 0.0_default_precision
180  pgacw_tot(:)= 0.0_default_precision
181  pgacs_tot(:)= 0.0_default_precision
182  pgmlt_tot(:)= 0.0_default_precision
183  pgsub_tot(:)= 0.0_default_precision
184  psedg_tot(:)= 0.0_default_precision
185  dqi_mphys_tot(:)= 0.0_default_precision
186  dqs_mphys_tot(:)= 0.0_default_precision
187  dqg_mphys_tot(:)= 0.0_default_precision
188  endif
189  endif
190 
191  if (.not. current_state%halo_column) then
192  if ( casdiags % l_psedl ) &
193  psedl_tot(:)= psedl_tot(:) + casim_monc_dgs % psedl(:,target_y_index,target_x_index)
194  if ( casdiags % l_pcond ) &
195  pcond_tot(:)= pcond_tot(:) + casim_monc_dgs % pcond(:,target_y_index,target_x_index)
196  if ( casdiags % l_praut ) &
197  praut_tot(:)= praut_tot(:) + casim_monc_dgs % praut(:,target_y_index,target_x_index)
198  if ( casdiags % l_pracw ) &
199  pracw_tot(:)= pracw_tot(:) + casim_monc_dgs % pracw(:,target_y_index,target_x_index)
200  if ( casdiags % l_prevp ) &
201  prevp_tot(:)= prevp_tot(:) + casim_monc_dgs % prevp(:,target_y_index,target_x_index)
202  if ( casdiags % l_psedr ) &
203  psedr_tot(:)= psedr_tot(:) + casim_monc_dgs % psedr(:,target_y_index,target_x_index)
204  if ( casdiags % l_dth ) then
205  dth_mphys_tot(:)= dth_mphys_tot(:) + &
206  casim_monc_dgs % dth_total(:,target_y_index,target_x_index)
207 
209  casim_monc_dgs % dth_cond_evap(:,target_y_index,target_x_index)
210  endif
211 
212  if ( casdiags % l_dqv ) then
213  dqv_mphys_tot(:)= dqv_mphys_tot(:) + &
214  casim_monc_dgs % dqv_total(:,target_y_index,target_x_index)
216  casim_monc_dgs % dqv_cond_evap(:,target_y_index,target_x_index)
217  endif
218 
219  if ( casdiags % l_dqc ) &
220  dqc_mphys_tot(:)= dqc_mphys_tot(:) + &
221  casim_monc_dgs % dqc(:,target_y_index,target_x_index)
222  if ( casdiags % l_dqr ) &
223  dqr_mphys_tot(:)= dqr_mphys_tot(:) + &
224  casim_monc_dgs % dqr(:,target_y_index,target_x_index)
225 
226  if (.not. l_warm) then
227  if ( casdiags % l_phomc ) &
228  phomc_tot(:)= phomc_tot(:) + &
229  casim_monc_dgs % phomc(:,target_y_index,target_x_index)
230  if ( casdiags % l_pinuc ) &
231  pinuc_tot(:)= pinuc_tot(:) + &
232  casim_monc_dgs % pinuc(:,target_y_index,target_x_index)
233  if ( casdiags % l_pidep ) &
234  pidep_tot(:)= pidep_tot(:) + &
235  casim_monc_dgs % pidep(:,target_y_index,target_x_index)
236  if ( casdiags % l_piacw ) &
237  piacw_tot(:)= piacw_tot(:) + &
238  casim_monc_dgs % piacw(:,target_y_index,target_x_index)
239  if ( casdiags % l_pisub ) &
240  pisub_tot(:)= pisub_tot(:) + &
241  casim_monc_dgs % pisub(:,target_y_index,target_x_index)
242  if ( casdiags % l_pimlt ) &
243  pimlt_tot(:)= pimlt_tot(:) + &
244  casim_monc_dgs % pimlt(:,target_y_index,target_x_index)
245  if ( casdiags % l_psedi ) &
246  psedi_tot(:)= psedi_tot(:) + &
247  casim_monc_dgs % psedi(:,target_y_index,target_x_index)
248  if ( casdiags % l_psacw ) &
249  psacw_tot(:)= psacw_tot(:) + &
250  casim_monc_dgs % psacw(:,target_y_index,target_x_index)
251  if ( casdiags % l_psacr ) &
252  psacr_tot(:)= psacr_tot(:) + &
253  casim_monc_dgs % psacr(:,target_y_index,target_x_index)
254  if ( casdiags % l_pssub ) &
255  pssub_tot(:)= pssub_tot(:) + &
256  casim_monc_dgs % pssub(:,target_y_index,target_x_index)
257  if ( casdiags % l_psmlt ) &
258  psmlt_tot(:)= psmlt_tot(:) + &
259  casim_monc_dgs % psmlt(:,target_y_index,target_x_index)
260  if ( casdiags % l_psaut ) &
261  psaut_tot(:)= psaut_tot(:) + &
262  casim_monc_dgs % psaut(:,target_y_index,target_x_index)
263  if ( casdiags % l_psaci ) &
264  psaci_tot(:)= psaci_tot(:) + &
265  casim_monc_dgs % psaci(:,target_y_index,target_x_index)
266  if ( casdiags % l_psdep ) &
267  psdep_tot(:)= psdep_tot(:) + &
268  casim_monc_dgs % psdep(:,target_y_index,target_x_index)
269  if ( casdiags % l_pseds ) &
270  pseds_tot(:)= pseds_tot(:) + &
271  casim_monc_dgs % pseds(:,target_y_index,target_x_index)
272  if ( casdiags % l_pgacw ) &
273  pgacw_tot(:)= pgacw_tot(:) + &
274  casim_monc_dgs % pgacw(:,target_y_index,target_x_index)
275  if ( casdiags % l_pgacs ) &
276  pgacs_tot(:)= pgacs_tot(:) + &
277  casim_monc_dgs % pgacs(:,target_y_index,target_x_index)
278  if ( casdiags % l_pgmlt ) &
279  pgmlt_tot(:)= pgmlt_tot(:) + &
280  casim_monc_dgs % pgmlt(:,target_y_index,target_x_index)
281  if ( casdiags % l_pgsub ) &
282  pgsub_tot(:)= pgsub_tot(:) + &
283  casim_monc_dgs % pgsub(:,target_y_index,target_x_index)
284  if ( casdiags % l_psedg ) &
285  psedg_tot(:)= psedg_tot(:) + &
286  casim_monc_dgs % psedg(:,target_y_index,target_x_index)
287  if ( casdiags % l_dqi ) &
288  dqi_mphys_tot(:)= dqi_mphys_tot(:) + &
289  casim_monc_dgs % dqi(:,target_y_index,target_x_index)
290  if ( casdiags % l_dqs ) &
291  dqs_mphys_tot(:)= dqs_mphys_tot(:) + &
292  casim_monc_dgs % dqs(:,target_y_index,target_x_index)
293  if ( casdiags % l_dqg ) &
294  dqg_mphys_tot(:)= dqg_mphys_tot(:) + &
295  casim_monc_dgs % dqg(:,target_y_index,target_x_index)
296  endif
297 
298  endif
299  end subroutine timestep_callback
300 
305  subroutine field_information_retrieval_callback(current_state, name, field_information)
306  type(model_state_type), target, intent(inout) :: current_state
307  character(len=*), intent(in) :: name
308  type(component_field_information_type), intent(out) :: field_information
309 
310  field_information%field_type=component_array_field_type
311  field_information%number_dimensions=1
312  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
313  field_information%data_type=component_double_data_type
314  if (l_warm) then
315  if (name .eq. "pcond_total" .or. name .eq. "praut_total" &
316  .or. name .eq. "pracw_total" .or. name .eq. "prevp_total" &
317  .or. name .eq. "psedl_total" .or. name .eq. "psedr_total" &
318  .or. name .eq. "dth_mphys_total" .or. name .eq. "dth_cond_evap_total" &
319  .or. name .eq. "dqv_mphys_total" .or. name .eq. "dqv_cond_evap_total" &
320  .or. name .eq. "dqc_mphys_total" .or. name .eq. "dqr_mphys_total") then
321  field_information%enabled=.true.
322  endif
323  else
324  field_information%enabled=.true.
325  endif
326 
328 
333  subroutine field_value_retrieval_callback(current_state, name, field_value)
334  type(model_state_type), target, intent(inout) :: current_state
335  character(len=*), intent(in) :: name
336  type(component_field_value_type), intent(out) :: field_value
337 
338  integer :: k
339 
340  if (name .eq. "phomc_total") then
341  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
342  field_value%real_1d_array(:)=phomc_tot(:)
343  else if (name .eq. "pinuc_total") then
344  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
345  field_value%real_1d_array(:)=pinuc_tot(:)
346  else if (name .eq. "pidep_total") then
347  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
348  field_value%real_1d_array(:)=pidep_tot(:)
349  else if (name .eq. "psdep_total") then
350  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
351  field_value%real_1d_array(:)=psdep_tot(:)
352  else if (name .eq. "piacw_total") then
353  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
354  field_value%real_1d_array(:)=piacw_tot(:)
355  else if (name .eq. "psacw_total") then
356  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
357  field_value%real_1d_array(:)=psacw_tot(:)
358  else if (name .eq. "psacr_total") then
359  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
360  field_value%real_1d_array(:)=psacr_tot(:)
361  else if (name .eq. "pisub_total") then
362  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
363  field_value%real_1d_array(:)=pisub_tot(:)
364  else if (name .eq. "pssub_total") then
365  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
366  field_value%real_1d_array(:)=pssub_tot(:)
367  else if (name .eq. "pimlt_total") then
368  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
369  field_value%real_1d_array(:)=pimlt_tot(:)
370  else if (name .eq. "psmlt_total") then
371  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
372  field_value%real_1d_array(:)=psmlt_tot(:)
373  else if (name .eq. "psaut_total") then
374  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
375  field_value%real_1d_array(:)=psaut_tot(:)
376  else if (name .eq. "psaci_total") then
377  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
378  field_value%real_1d_array(:)=psaci_tot(:)
379  else if (name .eq. "praut_total") then
380  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
381  field_value%real_1d_array(:)=praut_tot(:)
382  else if (name .eq. "pracw_total") then
383  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
384  field_value%real_1d_array(:)=pracw_tot(:)
385  else if (name .eq. "prevp_total") then
386  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
387  field_value%real_1d_array(:)=prevp_tot(:)
388  else if (name .eq. "pgacw_total") then
389  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
390  field_value%real_1d_array(:)=pgacw_tot(:)
391  else if (name .eq. "pgacs_total") then
392  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
393  field_value%real_1d_array(:)=pgacs_tot(:)
394  else if (name .eq. "pgmlt_total") then
395  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
396  field_value%real_1d_array(:)=pgmlt_tot(:)
397  else if (name .eq. "pgsub_total") then
398  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
399  field_value%real_1d_array(:)=pgsub_tot(:)
400  else if (name .eq. "psedi_total") then
401  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
402  field_value%real_1d_array(:)=psedi_tot(:)
403  else if (name .eq. "pseds_total") then
404  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
405  field_value%real_1d_array(:)=pseds_tot(:)
406  else if (name .eq. "psedr_total") then
407  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
408  field_value%real_1d_array(:)=psedr_tot(:)
409  else if (name .eq. "psedg_total") then
410  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
411  field_value%real_1d_array(:)=psedg_tot(:)
412  else if (name .eq. "psedl_total") then
413  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
414  field_value%real_1d_array(:)=psedl_tot(:)
415  else if (name .eq. "pcond_total") then
416  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
417  field_value%real_1d_array(:)=pcond_tot(:)
418  else if (name .eq. "dth_mphys_total") then
419  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
420  field_value%real_1d_array(:)=dth_mphys_tot(:)
421  else if (name .eq. "dth_cond_evap_total") then
422  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
423  field_value%real_1d_array(:)=dth_cond_evap_tot(:)
424  else if (name .eq. "dqv_mphys_total") then
425  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
426  field_value%real_1d_array(:)=dqv_mphys_tot(:)
427  else if (name .eq. "dqv_cond_evap_total") then
428  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
429  field_value%real_1d_array(:)=dqv_cond_evap_tot(:)
430  else if (name .eq. "dqc_mphys_total") then
431  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
432  field_value%real_1d_array(:)=dqc_mphys_tot(:)
433  else if (name .eq. "dqr_mphys_total") then
434  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
435  field_value%real_1d_array(:)=dqr_mphys_tot(:)
436  else if (name .eq. "dqi_mphys_total") then
437  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
438  field_value%real_1d_array(:)=dqi_mphys_tot(:)
439  else if (name .eq. "dqs_mphys_total") then
440  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
441  field_value%real_1d_array(:)=dqs_mphys_tot(:)
442  else if (name .eq. "dqg_mphys_total") then
443  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
444  field_value%real_1d_array(:)=dqg_mphys_tot(:)
445  endif
446  end subroutine field_value_retrieval_callback
447 end module casim_profile_dgs_mod
registry_mod::is_component_enabled
logical function, public is_component_enabled(options_database, component_name)
Determines whether or not a specific component is registered and enabled.
Definition: registry.F90:334
casim_profile_dgs_mod::pseds_tot
real(kind=default_precision), dimension(:), allocatable pseds_tot
Definition: casim_profile_dgs.F90:24
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
casim_profile_dgs_mod::dqg_mphys_tot
real(kind=default_precision), dimension(:), allocatable dqg_mphys_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::iqv
integer iqv
Definition: casim_profile_dgs.F90:23
casim_profile_dgs_mod::dth_cond_evap_tot
real(kind=default_precision), dimension(:), allocatable dth_cond_evap_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::praut_tot
real(kind=default_precision), dimension(:), allocatable praut_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::pimlt_tot
real(kind=default_precision), dimension(:), allocatable pimlt_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::prevp_tot
real(kind=default_precision), dimension(:), allocatable prevp_tot
Definition: casim_profile_dgs.F90:24
grids_mod::x_index
integer, parameter, public x_index
Definition: grids.F90:14
grids_mod::y_index
integer, parameter, public y_index
Definition: grids.F90:14
casim_profile_dgs_mod::dqr_mphys_tot
real(kind=default_precision), dimension(:), allocatable dqr_mphys_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::pinuc_tot
real(kind=default_precision), dimension(:), allocatable pinuc_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::total_points
integer total_points
Definition: casim_profile_dgs.F90:23
casim_profile_dgs_mod::psedr_tot
real(kind=default_precision), dimension(:), allocatable psedr_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::dqc_mphys_tot
real(kind=default_precision), dimension(:), allocatable dqc_mphys_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::piacw_tot
real(kind=default_precision), dimension(:), allocatable piacw_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::psaut_tot
real(kind=default_precision), dimension(:), allocatable psaut_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::psedi_tot
real(kind=default_precision), dimension(:), allocatable psedi_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::psacw_tot
real(kind=default_precision), dimension(:), allocatable psacw_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::phomc_tot
real(kind=default_precision), dimension(:), allocatable phomc_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::psedg_tot
real(kind=default_precision), dimension(:), allocatable psedg_tot
Definition: casim_profile_dgs.F90:24
monc_component_mod
Interfaces and types that MONC components must specify.
Definition: monc_component.F90:6
casim_profile_dgs_mod::psacr_tot
real(kind=default_precision), dimension(:), allocatable psacr_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::timestep_callback
subroutine timestep_callback(current_state)
Definition: casim_profile_dgs.F90:141
casim_profile_dgs_mod::pssub_tot
real(kind=default_precision), dimension(:), allocatable pssub_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::field_information_retrieval_callback
subroutine field_information_retrieval_callback(current_state, name, field_information)
Field information retrieval callback, this returns information for a specific components published fi...
Definition: casim_profile_dgs.F90:306
casim_profile_dgs_mod::pgsub_tot
real(kind=default_precision), dimension(:), allocatable pgsub_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::pcond_tot
real(kind=default_precision), dimension(:), allocatable pcond_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::pracw_tot
real(kind=default_precision), dimension(:), allocatable pracw_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::field_value_retrieval_callback
subroutine field_value_retrieval_callback(current_state, name, field_value)
Field value retrieval callback, this returns the value of a specific published field.
Definition: casim_profile_dgs.F90:334
casim_profile_dgs_mod::psedl_tot
real(kind=default_precision), dimension(:), allocatable psedl_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::casim_profile_dgs_get_descriptor
type(component_descriptor_type) function, public casim_profile_dgs_get_descriptor()
Provides the component descriptor for the core to register.
Definition: casim_profile_dgs.F90:41
casim_profile_dgs_mod::pidep_tot
real(kind=default_precision), dimension(:), allocatable pidep_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::dqv_cond_evap_tot
real(kind=default_precision), dimension(:), allocatable dqv_cond_evap_tot
Definition: casim_profile_dgs.F90:24
grids_mod::z_index
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
casim_profile_dgs_mod
Dummy stub when not compiling with CASIM microphysics.
Definition: casim_profile_dgs.F90:1
casim_profile_dgs_mod::psdep_tot
real(kind=default_precision), dimension(:), allocatable psdep_tot
Definition: casim_profile_dgs.F90:24
casim_monc_dgs_space
Definition: casim_monc_dgs_space.F90:1
casim_profile_dgs_mod::pgacs_tot
real(kind=default_precision), dimension(:), allocatable pgacs_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::initialisation_callback
subroutine initialisation_callback(current_state)
Definition: casim_profile_dgs.F90:91
casim_profile_dgs_mod::dth_mphys_tot
real(kind=default_precision), dimension(:), allocatable dth_mphys_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::pisub_tot
real(kind=default_precision), dimension(:), allocatable pisub_tot
Definition: casim_profile_dgs.F90:24
monc_component_mod::component_field_value_type
Wrapper type for the value returned for a published field from a component.
Definition: monc_component.F90:22
state_mod::model_state_type
The ModelState which represents the current state of a run.
Definition: state.F90:39
casim_profile_dgs_mod::psaci_tot
real(kind=default_precision), dimension(:), allocatable psaci_tot
Definition: casim_profile_dgs.F90:24
monc_component_mod::component_field_information_type
Definition: monc_component.F90:31
casim_profile_dgs_mod::psmlt_tot
real(kind=default_precision), dimension(:), allocatable psmlt_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::pgacw_tot
real(kind=default_precision), dimension(:), allocatable pgacw_tot
Definition: casim_profile_dgs.F90:24
logging_mod
Logging utility.
Definition: logging.F90:2
datadefn_mod
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
registry_mod
MONC component registry.
Definition: registry.F90:5
casim_profile_dgs_mod::dqi_mphys_tot
real(kind=default_precision), dimension(:), allocatable dqi_mphys_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::iql
integer iql
Definition: casim_profile_dgs.F90:23
grids_mod
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
casim_profile_dgs_mod::dqv_mphys_tot
real(kind=default_precision), dimension(:), allocatable dqv_mphys_tot
Definition: casim_profile_dgs.F90:24
casim_profile_dgs_mod::dqs_mphys_tot
real(kind=default_precision), dimension(:), allocatable dqs_mphys_tot
Definition: casim_profile_dgs.F90:24
casim_monc_dgs_space::casim_monc_dgs
type(casim_monc_dglist) casim_monc_dgs
Definition: casim_monc_dgs_space.F90:80
monc_component_mod::component_descriptor_type
Description of a component.
Definition: monc_component.F90:42
monc_component_mod::component_double_data_type
integer, parameter, public component_double_data_type
Definition: monc_component.F90:16
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
state_mod
The model state which represents the current state of a run.
Definition: state.F90:2
monc_component_mod::component_array_field_type
integer, parameter, public component_array_field_type
Definition: monc_component.F90:15
casim_profile_dgs_mod::pgmlt_tot
real(kind=default_precision), dimension(:), allocatable pgmlt_tot
Definition: casim_profile_dgs.F90:24