MONC
flux_budget.F90
Go to the documentation of this file.
1 
11  use state_mod, only : model_state_type
12 
13  implicit none
14 
15 #ifndef TEST_MODE
16  private
17 #endif
18 
19  real(kind=DEFAULT_PRECISION), dimension(:), allocatable :: th_flux_values, th_gradient, th_diff, th_buoyancy, th_tendency, &
31  real(kind=DEFAULT_PRECISION) :: mflux, wmfcrit
32  real(kind=DEFAULT_PRECISION), dimension(:,:), allocatable :: q_flux_values, q_gradient, q_diff, q_buoyancy, q_tendency
35 
40 
42 contains
43 
47  type(iterator_type) :: iterator
48  type(mapentry_type) :: mapentry
49  integer :: current_index, total_number_published_fields
50 
51  flux_budget_get_descriptor%name="flux_budget"
52  flux_budget_get_descriptor%version=0.1
56 
60  total_number_published_fields=c_size(heat_flux_fields)+c_size(q_flux_fields)+c_size(uw_vw_fields)+&
62  allocate(flux_budget_get_descriptor%published_fields(total_number_published_fields))
63 
64  current_index=1
66  do while (c_has_next(iterator))
67  mapentry=c_next_mapentry(iterator)
68  flux_budget_get_descriptor%published_fields(current_index)=mapentry%key
69  current_index=current_index+1
70  end do
72  do while (c_has_next(iterator))
73  mapentry=c_next_mapentry(iterator)
74  flux_budget_get_descriptor%published_fields(current_index)=mapentry%key
75  current_index=current_index+1
76  end do
78  do while (c_has_next(iterator))
79  mapentry=c_next_mapentry(iterator)
80  flux_budget_get_descriptor%published_fields(current_index)=mapentry%key
81  current_index=current_index+1
82  end do
84  do while (c_has_next(iterator))
85  mapentry=c_next_mapentry(iterator)
86  flux_budget_get_descriptor%published_fields(current_index)=mapentry%key
87  current_index=current_index+1
88  end do
90  do while (c_has_next(iterator))
91  mapentry=c_next_mapentry(iterator)
92  flux_budget_get_descriptor%published_fields(current_index)=mapentry%key
93  current_index=current_index+1
94  end do
95  iterator=c_get_iterator(mse_fields)
96  do while (c_has_next(iterator))
97  mapentry=c_next_mapentry(iterator)
98  flux_budget_get_descriptor%published_fields(current_index)=mapentry%key
99  current_index=current_index+1
100  end do
101  iterator=c_get_iterator(qt_fields)
102  do while (c_has_next(iterator))
103  mapentry=c_next_mapentry(iterator)
104  flux_budget_get_descriptor%published_fields(current_index)=mapentry%key
105  current_index=current_index+1
106  end do
107  iterator=c_get_iterator(scalar_fields)
108  do while (c_has_next(iterator))
109  mapentry=c_next_mapentry(iterator)
110  flux_budget_get_descriptor%published_fields(current_index)=mapentry%key
111  current_index=current_index+1
112  end do
113  end function flux_budget_get_descriptor
114 
117  subroutine initialisation_callback(current_state)
118  type(model_state_type), target, intent(inout) :: current_state
119 
120  call initialise_theta_flux_diagnostics(current_state)
121  call initialise_q_flux_diagnostics(current_state)
122  call initialise_uw_vw_diagnostics(current_state)
123  call initialise_prognostic_budget_diagnostics(current_state)
124  call initialise_thetal_diagnostics(current_state)
125  call initialise_mse_diagnostics(current_state)
126  call initialise_qt_diagnostics(current_state)
127  call initialise_scalar_diagnostics(current_state)
128  diagnostic_generation_frequency=options_get_integer(current_state%options_database, "sampling_frequency")
129  end subroutine initialisation_callback
130 
133  subroutine timestep_callback(current_state)
134  type(model_state_type), target, intent(inout) :: current_state
135 
136  if (mod(current_state%timestep, diagnostic_generation_frequency) == 0) then
137  if (current_state%first_timestep_column) then
145  call clear_scalars()
146  end if
147  if (.not. current_state%halo_column) then
154  if (some_qt_diagnostics_enabled) call compute_qt_for_column(current_state)
155  call compute_scalars_for_column(current_state)
156  end if
157  end if
158  end subroutine timestep_callback
159 
162  subroutine finalisation_callback(current_state)
163  type(model_state_type), target, intent(inout) :: current_state
164 
165  if (allocated(th_flux_values)) deallocate(th_flux_values)
166  if (allocated(th_gradient)) deallocate(th_gradient)
167  if (allocated(th_diff)) deallocate(th_diff)
168  if (allocated(th_buoyancy)) deallocate(th_buoyancy)
169  if (allocated(th_tendency)) deallocate(th_tendency)
170  if (allocated(q_flux_values)) deallocate(q_flux_values)
171  if (allocated(q_gradient)) deallocate(q_gradient)
172  if (allocated(q_diff)) deallocate(q_diff)
173  if (allocated(q_buoyancy)) deallocate(q_buoyancy)
174  if (allocated(q_tendency)) deallocate(q_tendency)
175 
176  if (allocated(uw_advection)) deallocate(uw_advection)
177  if (allocated(vw_advection)) deallocate(vw_advection)
178  if (allocated(uw_viscosity)) deallocate(uw_viscosity)
179  if (allocated(vw_viscosity)) deallocate(vw_viscosity)
180  if (allocated(uw_buoyancy)) deallocate(uw_buoyancy)
181  if (allocated(vw_buoyancy)) deallocate(vw_buoyancy)
182  if (allocated(uw_tendency)) deallocate(uw_tendency)
183  if (allocated(vw_tendency)) deallocate(vw_tendency)
184  if (allocated(uw_w)) deallocate(uw_w)
185  if (allocated(vw_w)) deallocate(vw_w)
186 
187  if (allocated(tu_su)) deallocate(tu_su)
188  if (allocated(uu_advection)) deallocate(uu_advection)
189  if (allocated(uu_viscosity)) deallocate(uu_viscosity)
190  if (allocated(wu_u)) deallocate(wu_u)
191  if (allocated(tv_sv)) deallocate(tv_sv)
192  if (allocated(vv_advection)) deallocate(vv_advection)
193  if (allocated(vv_viscosity)) deallocate(vv_viscosity)
194  if (allocated(wv_v)) deallocate(wv_v)
195  if (allocated(tw_sw)) deallocate(tw_sw)
196  if (allocated(ww_advection)) deallocate(ww_advection)
197  if (allocated(ww_viscosity)) deallocate(ww_viscosity)
198  if (allocated(ww_buoyancy)) deallocate(ww_buoyancy)
199 
200  if (allocated(u_thetal)) deallocate(u_thetal)
201  if (allocated(us_thetal)) deallocate(us_thetal)
202  if (allocated(u_thetal_advection)) deallocate(u_thetal_advection)
204  if (allocated(wu_thetal)) deallocate(wu_thetal)
205  if (allocated(v_thetal)) deallocate(v_thetal)
206  if (allocated(vs_thetal)) deallocate(vs_thetal)
207  if (allocated(v_thetal_advection)) deallocate(v_thetal_advection)
209  if (allocated(wv_thetal)) deallocate(wv_thetal)
210  if (allocated(w_thetal)) deallocate(w_thetal)
211  if (allocated(ws_thetal)) deallocate(ws_thetal)
212  if (allocated(w_thetal_advection)) deallocate(w_thetal_advection)
214  if (allocated(w_thetal_buoyancy)) deallocate(w_thetal_buoyancy)
215  if (allocated(ww_thetal)) deallocate(ww_thetal)
216  if (allocated(thetal_thetal)) deallocate(thetal_thetal)
217  if (allocated(sthetal_thetal)) deallocate(sthetal_thetal)
218  if (allocated(thetal_thetal_advection)) deallocate(thetal_thetal_advection)
219  if (allocated(thetal_thetal_diffusion)) deallocate(thetal_thetal_diffusion)
220  if (allocated(wthetal_thetal)) deallocate(wthetal_thetal)
221 
222  if (allocated(u_mse)) deallocate(u_mse)
223  if (allocated(us_mse)) deallocate(us_mse)
224  if (allocated(u_mse_advection)) deallocate(u_mse_advection)
225  if (allocated(u_mse_viscosity_diffusion)) deallocate(u_mse_viscosity_diffusion)
226  if (allocated(wu_mse)) deallocate(wu_mse)
227  if (allocated(v_mse)) deallocate(v_mse)
228  if (allocated(vs_mse)) deallocate(vs_mse)
229  if (allocated(v_mse_advection)) deallocate(v_mse_advection)
230  if (allocated(v_mse_viscosity_diffusion)) deallocate(v_mse_viscosity_diffusion)
231  if (allocated(wv_mse)) deallocate(wv_mse)
232  if (allocated(w_mse)) deallocate(w_mse)
233  if (allocated(ws_mse)) deallocate(ws_mse)
234  if (allocated(w_mse_advection)) deallocate(w_mse_advection)
235  if (allocated(w_mse_viscosity_diffusion)) deallocate(w_mse_viscosity_diffusion)
236  if (allocated(w_mse_buoyancy)) deallocate(w_mse_buoyancy)
237  if (allocated(ww_mse)) deallocate(ww_mse)
238  if (allocated(mse_mse)) deallocate(mse_mse)
239  if (allocated(smse_mse)) deallocate(smse_mse)
240  if (allocated(mse_mse_advection)) deallocate(mse_mse_advection)
241  if (allocated(mse_mse_diffusion)) deallocate(mse_mse_diffusion)
242  if (allocated(wmse_mse)) deallocate(wmse_mse)
243 
244  if (allocated(us_qt)) deallocate(us_qt)
245  if (allocated(u_qt_advection)) deallocate(u_qt_advection)
246  if (allocated(u_qt_viscosity_diffusion)) deallocate(u_qt_viscosity_diffusion)
247  if (allocated(wu_qt)) deallocate(wu_qt)
248  if (allocated(vs_qt)) deallocate(vs_qt)
249  if (allocated(v_qt_advection)) deallocate(v_qt_advection)
250  if (allocated(v_qt_viscosity_diffusion)) deallocate(v_qt_viscosity_diffusion)
251  if (allocated(wv_qt)) deallocate(wv_qt)
252  if (allocated(w_qt)) deallocate(w_qt)
253  if (allocated(ws_qt)) deallocate(ws_qt)
254  if (allocated(w_qt_advection)) deallocate(w_qt_advection)
255  if (allocated(w_qt_viscosity_diffusion)) deallocate(w_qt_viscosity_diffusion)
256  if (allocated(w_qt_buoyancy)) deallocate(w_qt_buoyancy)
257  if (allocated(ww_qt)) deallocate(ww_qt)
258  if (allocated(qt_qt)) deallocate(qt_qt)
259  if (allocated(sqt_qt)) deallocate(sqt_qt)
260  if (allocated(qt_qt_advection)) deallocate(qt_qt_advection)
261  if (allocated(qt_qt_diffusion)) deallocate(qt_qt_diffusion)
262  if (allocated(wqt_qt)) deallocate(wqt_qt)
263  end subroutine finalisation_callback
264 
266  subroutine populate_field_names()
267  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_transport_local", .false.)
268  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_gradient_local", .false.)
269  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_dissipation_local", .false.)
270  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_buoyancy_local", .false.)
271  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_tendency_local", .false.)
272 
273  call set_published_field_enabled_state(q_flux_fields, "q_flux_transport_local", .false.)
274  call set_published_field_enabled_state(q_flux_fields, "q_flux_gradient_local", .false.)
275  call set_published_field_enabled_state(q_flux_fields, "q_flux_dissipation_local", .false.)
276  call set_published_field_enabled_state(q_flux_fields, "q_flux_buoyancy_local", .false.)
277  call set_published_field_enabled_state(q_flux_fields, "q_flux_tendency_local", .false.)
278 
279  call set_published_field_enabled_state(uw_vw_fields, "uw_advection_local", .false.)
280  call set_published_field_enabled_state(uw_vw_fields, "vw_advection_local", .false.)
281  call set_published_field_enabled_state(uw_vw_fields, "uw_viscosity_local", .false.)
282  call set_published_field_enabled_state(uw_vw_fields, "vw_viscosity_local", .false.)
283  call set_published_field_enabled_state(uw_vw_fields, "uw_buoyancy_local", .false.)
284  call set_published_field_enabled_state(uw_vw_fields, "vw_buoyancy_local", .false.)
285  call set_published_field_enabled_state(uw_vw_fields, "uw_tendency_local", .false.)
286  call set_published_field_enabled_state(uw_vw_fields, "vw_tendency_local", .false.)
287  call set_published_field_enabled_state(uw_vw_fields, "uw_w_local", .false.)
288  call set_published_field_enabled_state(uw_vw_fields, "vw_w_local", .false.)
289 
290  call set_published_field_enabled_state(prognostic_budget_fields, "tu_su_local", .false.)
291  call set_published_field_enabled_state(prognostic_budget_fields, "uu_advection_local", .false.)
292  call set_published_field_enabled_state(prognostic_budget_fields, "uu_viscosity_local", .false.)
294  call set_published_field_enabled_state(prognostic_budget_fields, "tv_sv_local", .false.)
295  call set_published_field_enabled_state(prognostic_budget_fields, "vv_advection_local", .false.)
296  call set_published_field_enabled_state(prognostic_budget_fields, "vv_viscosity_local", .false.)
298  call set_published_field_enabled_state(prognostic_budget_fields, "tw_sw_local", .false.)
299  call set_published_field_enabled_state(prognostic_budget_fields, "ww_advection_local", .false.)
300  call set_published_field_enabled_state(prognostic_budget_fields, "ww_viscosity_local", .false.)
301  call set_published_field_enabled_state(prognostic_budget_fields, "ww_buoyancy_local", .false.)
302 
303  call set_published_field_enabled_state(thetal_fields, "u_thetal_local", .false.)
304  call set_published_field_enabled_state(thetal_fields, "us_thetal_local", .false.)
305  call set_published_field_enabled_state(thetal_fields, "u_thetal_advection_local", .false.)
306  call set_published_field_enabled_state(thetal_fields, "u_thetal_viscosity_diffusion_local", .false.)
307  call set_published_field_enabled_state(thetal_fields, "wu_thetal_local", .false.)
308  call set_published_field_enabled_state(thetal_fields, "v_thetal_local", .false.)
309  call set_published_field_enabled_state(thetal_fields, "vs_thetal_local", .false.)
310  call set_published_field_enabled_state(thetal_fields, "v_thetal_advection_local", .false.)
311  call set_published_field_enabled_state(thetal_fields, "v_thetal_viscosity_diffusion_local", .false.)
312  call set_published_field_enabled_state(thetal_fields, "wv_thetal_local", .false.)
313  call set_published_field_enabled_state(thetal_fields, "w_thetal_local", .false.)
314  call set_published_field_enabled_state(thetal_fields, "ws_thetal_local", .false.)
315  call set_published_field_enabled_state(thetal_fields, "w_thetal_advection_local", .false.)
316  call set_published_field_enabled_state(thetal_fields, "w_thetal_viscosity_diffusion_local", .false.)
317  call set_published_field_enabled_state(thetal_fields, "ww_thetal_buoyancy_local", .false.)
318  call set_published_field_enabled_state(thetal_fields, "ww_thetal_local", .false.)
319  call set_published_field_enabled_state(thetal_fields, "thetal_thetal_local", .false.)
320  call set_published_field_enabled_state(thetal_fields, "sthetal_thetal_local", .false.)
321  call set_published_field_enabled_state(thetal_fields, "thetal_thetal_advection_local", .false.)
322  call set_published_field_enabled_state(thetal_fields, "thetal_thetal_diffusion_local", .false.)
323  call set_published_field_enabled_state(thetal_fields, "wthetal_thetal_local", .false.)
324 
325  call set_published_field_enabled_state(mse_fields, "u_mse_local", .false.)
326  call set_published_field_enabled_state(mse_fields, "us_mse_local", .false.)
327  call set_published_field_enabled_state(mse_fields, "u_mse_advection_local", .false.)
328  call set_published_field_enabled_state(mse_fields, "u_mse_viscosity_diffusion_local", .false.)
329  call set_published_field_enabled_state(mse_fields, "wu_mse_local", .false.)
330  call set_published_field_enabled_state(mse_fields, "v_mse_local", .false.)
331  call set_published_field_enabled_state(mse_fields, "vs_mse_local", .false.)
332  call set_published_field_enabled_state(mse_fields, "v_mse_advection_local", .false.)
333  call set_published_field_enabled_state(mse_fields, "v_mse_viscosity_diffusion_local", .false.)
334  call set_published_field_enabled_state(mse_fields, "wv_mse_local", .false.)
335  call set_published_field_enabled_state(mse_fields, "w_mse_local", .false.)
336  call set_published_field_enabled_state(mse_fields, "ws_mse_local", .false.)
337  call set_published_field_enabled_state(mse_fields, "w_mse_advection_local", .false.)
338  call set_published_field_enabled_state(mse_fields, "w_mse_viscosity_diffusion_local", .false.)
339  call set_published_field_enabled_state(mse_fields, "ww_mse_buoyancy_local", .false.)
340  call set_published_field_enabled_state(mse_fields, "ww_mse_local", .false.)
341  call set_published_field_enabled_state(mse_fields, "mse_mse_local", .false.)
342  call set_published_field_enabled_state(mse_fields, "smse_mse_local", .false.)
343  call set_published_field_enabled_state(mse_fields, "mse_mse_advection_local", .false.)
344  call set_published_field_enabled_state(mse_fields, "mse_mse_diffusion_local", .false.)
345  call set_published_field_enabled_state(mse_fields, "wmse_mse_local", .false.)
346 
347  call set_published_field_enabled_state(qt_fields, "us_qt_local", .false.)
348  call set_published_field_enabled_state(qt_fields, "u_qt_advection_local", .false.)
349  call set_published_field_enabled_state(qt_fields, "u_qt_viscosity_diffusion_local", .false.)
350  call set_published_field_enabled_state(qt_fields, "wu_qt_local", .false.)
351  call set_published_field_enabled_state(qt_fields, "vs_qt_local", .false.)
352  call set_published_field_enabled_state(qt_fields, "v_qt_advection_local", .false.)
353  call set_published_field_enabled_state(qt_fields, "v_qt_viscosity_diffusion_local", .false.)
354  call set_published_field_enabled_state(qt_fields, "wv_qt_local", .false.)
355  call set_published_field_enabled_state(qt_fields, "w_qt_local", .false.)
356  call set_published_field_enabled_state(qt_fields, "ws_qt_local", .false.)
357  call set_published_field_enabled_state(qt_fields, "w_qt_advection_local", .false.)
358  call set_published_field_enabled_state(qt_fields, "w_qt_viscosity_diffusion_local", .false.)
359  call set_published_field_enabled_state(qt_fields, "ww_qt_buoyancy_local", .false.)
360  call set_published_field_enabled_state(qt_fields, "ww_qt_local", .false.)
361  call set_published_field_enabled_state(qt_fields, "qt_qt_local", .false.)
362  call set_published_field_enabled_state(qt_fields, "sqt_qt_local", .false.)
363  call set_published_field_enabled_state(qt_fields, "qt_qt_advection_local", .false.)
364  call set_published_field_enabled_state(qt_fields, "qt_qt_diffusion_local", .false.)
365  call set_published_field_enabled_state(qt_fields, "wqt_qt_local", .false.)
366 
367  call set_published_field_enabled_state(scalar_fields, "mflux_local", .true.)
368  end subroutine populate_field_names
369 
374  subroutine field_information_retrieval_callback(current_state, name, field_information)
375  type(model_state_type), target, intent(inout) :: current_state
376  character(len=*), intent(in) :: name
377  type(component_field_information_type), intent(out) :: field_information
378 
379  ! Field description is the same regardless of the specific field being retrieved
380  field_information%field_type=component_array_field_type
381  field_information%data_type=component_double_data_type
382 
383  if (is_field_heat_flux(name) .or. is_field_uw_vw(name) .or. is_field_prognostic_budget(name) &
384  .or. is_field_thetal(name) .or. is_field_mse(name) .or. is_field_qt(name) .or. is_field_scalar(name)) then
385  field_information%number_dimensions=1
386  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
387  if (is_field_heat_flux(name)) then
388  field_information%enabled=get_published_field_enabled_state(heat_flux_fields, name)
389  else if (is_field_uw_vw(name)) then
390  field_information%enabled=get_published_field_enabled_state(uw_vw_fields, name)
391  else if (is_field_prognostic_budget(name)) then
392  field_information%enabled=get_published_field_enabled_state(prognostic_budget_fields, name)
393  else if (is_field_thetal(name)) then
394  field_information%enabled=get_published_field_enabled_state(thetal_fields, name)
395  else if (is_field_mse(name)) then
396  field_information%enabled=get_published_field_enabled_state(mse_fields, name)
397  else if (is_field_qt(name)) then
398  field_information%enabled=get_published_field_enabled_state(qt_fields, name)
399  else if (is_field_scalar(name)) then
400  field_information%enabled=get_published_field_enabled_state(scalar_fields, name)
401  end if
402  else if (is_field_q_flux(name)) then
403  field_information%number_dimensions=2
404  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
405  field_information%dimension_sizes(2)=current_state%number_q_fields
406  field_information%enabled=get_published_field_enabled_state(q_flux_fields, name)
407  end if
409 
412  subroutine initialise_scalar_diagnostics(current_state)
413  type(model_state_type), target, intent(inout) :: current_state
414 
415  wmfcrit=options_get_real(current_state%options_database, "wmfcrit")
416  end subroutine initialise_scalar_diagnostics
417 
421  subroutine initialise_qt_diagnostics(current_state)
422  type(model_state_type), target, intent(inout) :: current_state
423 
424  integer :: column_size
425  logical :: us_qt_enabled, u_qt_advection_enabled, u_qt_viscosity_diffusion_enabled, &
426  wu_qt_enabled, vs_qt_enabled, v_qt_advection_enabled, &
427  v_qt_viscosity_diffusion_enabled, wv_qt_enabled, w_qt_enabled, ws_qt_enabled, &
428  w_qt_advection_enabled, w_qt_viscosity_diffusion_enabled, w_qt_buoyancy_enabled, ww_qt_enabled, &
429  qt_qt_enabled, sqt_qt_enabled, qt_qt_advection_enabled, &
430  qt_qt_diffusion_enabled, wqt_qt_enabled
431 
432  column_size=current_state%local_grid%size(z_index)
433 
434  us_qt_enabled=current_state%u%active .and. current_state%th%active
435  u_qt_advection_enabled=is_component_field_available("u_advection") .and. &
436  is_component_field_available("th_advection") .and. us_qt_enabled
437  u_qt_viscosity_diffusion_enabled=is_component_field_available("u_viscosity") .and. &
438  is_component_field_available("th_diffusion") .and. us_qt_enabled
439  wu_qt_enabled=current_state%w%active .and. us_qt_enabled
440 
441  some_qt_diagnostics_enabled=us_qt_enabled
442 
443  if (us_qt_enabled) then
444  call set_published_field_enabled_state(qt_fields, "us_qt_local", .true.)
445  allocate(us_qt(column_size))
446  end if
447  if (u_qt_advection_enabled) then
448  call set_published_field_enabled_state(qt_fields, "u_qt_advection_local", .true.)
449  allocate(u_qt_advection(column_size))
450  end if
451  if (u_qt_viscosity_diffusion_enabled) then
452  call set_published_field_enabled_state(qt_fields, "u_qt_viscosity_diffusion_local", .true.)
453  allocate(u_qt_viscosity_diffusion(column_size))
454  end if
455  if (wu_qt_enabled) then
456  call set_published_field_enabled_state(qt_fields, "wu_qt_local", .true.)
457  allocate(wu_qt(column_size))
458  end if
459 
460  vs_qt_enabled=current_state%v%active .and. current_state%th%active
461  v_qt_advection_enabled=is_component_field_available("v_advection") .and. &
462  is_component_field_available("th_advection") .and. vs_qt_enabled
463  v_qt_viscosity_diffusion_enabled=is_component_field_available("v_viscosity") .and. &
464  is_component_field_available("th_diffusion") .and. vs_qt_enabled
465  wv_qt_enabled=current_state%w%active .and. vs_qt_enabled
466 
468 
469  if (vs_qt_enabled) then
470  call set_published_field_enabled_state(qt_fields, "vs_qt_local", .true.)
471  allocate(vs_qt(column_size))
472  end if
473  if (v_qt_advection_enabled) then
474  call set_published_field_enabled_state(qt_fields, "v_qt_advection_local", .true.)
475  allocate(v_qt_advection(column_size))
476  end if
477  if (v_qt_viscosity_diffusion_enabled) then
478  call set_published_field_enabled_state(qt_fields, "v_qt_viscosity_diffusion_local", .true.)
479  allocate(v_qt_viscosity_diffusion(column_size))
480  end if
481  if (wv_qt_enabled) then
482  call set_published_field_enabled_state(qt_fields, "wv_qt_local", .true.)
483  allocate(wv_qt(column_size))
484  end if
485 
486  w_qt_enabled=current_state%w%active .and. current_state%th%active
487  ws_qt_enabled=w_qt_enabled
488  w_qt_advection_enabled=is_component_field_available("w_advection") .and. &
489  is_component_field_available("th_advection") .and. w_qt_enabled
490  w_qt_viscosity_diffusion_enabled=is_component_field_available("w_viscosity") .and. &
491  is_component_field_available("th_diffusion") .and. w_qt_enabled
492  w_qt_buoyancy_enabled=current_state%th%active .and. is_component_field_available("w_buoyancy")
493  ww_qt_enabled=w_qt_enabled
494 
496 
497  if (w_qt_enabled) then
498  call set_published_field_enabled_state(qt_fields, "w_qt_local", .true.)
499  allocate(w_qt(column_size))
500  end if
501  if (ws_qt_enabled) then
502  call set_published_field_enabled_state(qt_fields, "ws_qt_local", .true.)
503  allocate(ws_qt(column_size))
504  end if
505  if (w_qt_advection_enabled) then
506  call set_published_field_enabled_state(qt_fields, "w_qt_advection_local", .true.)
507  allocate(w_qt_advection(column_size))
508  end if
509  if (w_qt_viscosity_diffusion_enabled) then
510  call set_published_field_enabled_state(qt_fields, "w_qt_viscosity_diffusion_local", .true.)
511  allocate(w_qt_viscosity_diffusion(column_size))
512  end if
513  if (w_qt_buoyancy_enabled) then
514  call set_published_field_enabled_state(qt_fields, "w_qt_buoyancy_local", .true.)
515  allocate(w_qt_buoyancy(column_size))
516  end if
517  if (ww_qt_enabled) then
518  call set_published_field_enabled_state(qt_fields, "ww_qt_local", .true.)
519  allocate(ww_qt(column_size))
520  end if
521 
522  qt_qt_enabled=current_state%th%active
523  sqt_qt_enabled=qt_qt_enabled
524  qt_qt_advection_enabled=is_component_field_available("qt_advection") .and. qt_qt_enabled
525  qt_qt_diffusion_enabled=is_component_field_available("qt_diffusion") .and. qt_qt_enabled
526  wqt_qt_enabled=current_state%w%active .and. qt_qt_enabled
527 
529 
530  if (qt_qt_enabled) then
531  call set_published_field_enabled_state(qt_fields, "qt_qt_local", .true.)
532  allocate(qt_qt(column_size))
533  end if
534  if (sqt_qt_enabled) then
535  call set_published_field_enabled_state(qt_fields, "sqt_qt_local", .true.)
536  allocate(sqt_qt(column_size))
537  end if
538  if (qt_qt_advection_enabled) then
539  call set_published_field_enabled_state(qt_fields, "qt_qt_advection_local", .true.)
540  allocate(qt_qt_advection(column_size))
541  end if
542  if (qt_qt_diffusion_enabled) then
543  call set_published_field_enabled_state(qt_fields, "qt_qt_diffusion_local", .true.)
544  allocate(qt_qt_diffusion(column_size))
545  end if
546  if (wqt_qt_enabled) then
547  call set_published_field_enabled_state(qt_fields, "wqt_qt_local", .true.)
548  allocate(wqt_qt(column_size))
549  end if
550  end subroutine initialise_qt_diagnostics
551 
555  subroutine initialise_mse_diagnostics(current_state)
556  type(model_state_type), target, intent(inout) :: current_state
557 
558  integer :: column_size
559  logical :: u_mse_enabled, us_mse_enabled, u_mse_advection_enabled, u_mse_viscosity_diffusion_enabled, &
560  wu_mse_enabled, v_mse_enabled, vs_mse_enabled, v_mse_advection_enabled, &
561  v_mse_viscosity_diffusion_enabled, wv_mse_enabled, w_mse_enabled, ws_mse_enabled, &
562  w_mse_advection_enabled, w_mse_viscosity_diffusion_enabled, w_mse_buoyancy_enabled, ww_mse_enabled, &
563  mse_mse_enabled, smse_mse_enabled, mse_mse_advection_enabled, &
564  mse_mse_diffusion_enabled, wmse_mse_enabled
565 
566  column_size=current_state%local_grid%size(z_index)
567 
568  u_mse_enabled=current_state%u%active .and. current_state%th%active
569  us_mse_enabled=u_mse_enabled
570  u_mse_advection_enabled=is_component_field_available("u_advection") .and. &
571  is_component_field_available("th_advection") .and. u_mse_enabled
572  u_mse_viscosity_diffusion_enabled=is_component_field_available("u_viscosity") .and. &
573  is_component_field_available("th_diffusion") .and. u_mse_enabled
574  wu_mse_enabled=current_state%w%active .and. u_mse_enabled
575 
576  some_mse_diagnostics_enabled=u_mse_enabled
577 
578  if (u_mse_enabled) then
579  call set_published_field_enabled_state(mse_fields, "u_mse_local", .true.)
580  allocate(u_mse(column_size))
581  end if
582  if (us_mse_enabled) then
583  call set_published_field_enabled_state(mse_fields, "us_mse_local", .true.)
584  allocate(us_mse(column_size))
585  end if
586  if (u_mse_advection_enabled) then
587  call set_published_field_enabled_state(mse_fields, "u_mse_advection_local", .true.)
588  allocate(u_mse_advection(column_size))
589  end if
590  if (u_mse_viscosity_diffusion_enabled) then
591  call set_published_field_enabled_state(mse_fields, "u_mse_viscosity_diffusion_local", .true.)
592  allocate(u_mse_viscosity_diffusion(column_size))
593  end if
594  if (wu_mse_enabled) then
595  call set_published_field_enabled_state(mse_fields, "wu_mse_local", .true.)
596  allocate(wu_mse(column_size))
597  end if
598 
599  v_mse_enabled=current_state%v%active .and. current_state%th%active
600  vs_mse_enabled=v_mse_enabled
601  v_mse_advection_enabled=is_component_field_available("v_advection") .and. &
602  is_component_field_available("th_advection") .and. v_mse_enabled
603  v_mse_viscosity_diffusion_enabled=is_component_field_available("v_viscosity") .and. &
604  is_component_field_available("th_diffusion") .and. v_mse_enabled
605  wv_mse_enabled=current_state%w%active .and. v_mse_enabled
606 
608 
609  if (v_mse_enabled) then
610  call set_published_field_enabled_state(mse_fields, "v_mse_local", .true.)
611  allocate(v_mse(column_size))
612  end if
613  if (vs_mse_enabled) then
614  call set_published_field_enabled_state(mse_fields, "vs_mse_local", .true.)
615  allocate(vs_mse(column_size))
616  end if
617  if (v_mse_advection_enabled) then
618  call set_published_field_enabled_state(mse_fields, "v_mse_advection_local", .true.)
619  allocate(v_mse_advection(column_size))
620  end if
621  if (v_mse_viscosity_diffusion_enabled) then
622  call set_published_field_enabled_state(mse_fields, "v_mse_viscosity_diffusion_local", .true.)
623  allocate(v_mse_viscosity_diffusion(column_size))
624  end if
625  if (wv_mse_enabled) then
626  call set_published_field_enabled_state(mse_fields, "wv_mse_local", .true.)
627  allocate(wv_mse(column_size))
628  end if
629 
630  w_mse_enabled=current_state%w%active .and. current_state%th%active
631  ws_mse_enabled=w_mse_enabled
632  w_mse_advection_enabled=is_component_field_available("w_advection") .and. &
633  is_component_field_available("th_advection") .and. w_mse_enabled
634  w_mse_viscosity_diffusion_enabled=is_component_field_available("w_viscosity") .and. &
635  is_component_field_available("th_diffusion") .and. w_mse_enabled
636  w_mse_buoyancy_enabled=current_state%th%active .and. is_component_field_available("w_buoyancy")
637  ww_mse_enabled=w_mse_enabled
638 
640 
641  if (w_mse_enabled) then
642  call set_published_field_enabled_state(mse_fields, "w_mse_local", .true.)
643  allocate(w_mse(column_size))
644  end if
645  if (ws_mse_enabled) then
646  call set_published_field_enabled_state(mse_fields, "ws_mse_local", .true.)
647  allocate(ws_mse(column_size))
648  end if
649  if (w_mse_advection_enabled) then
650  call set_published_field_enabled_state(mse_fields, "w_mse_advection_local", .true.)
651  allocate(w_mse_advection(column_size))
652  end if
653  if (w_mse_viscosity_diffusion_enabled) then
654  call set_published_field_enabled_state(mse_fields, "w_mse_viscosity_diffusion_local", .true.)
655  allocate(w_mse_viscosity_diffusion(column_size))
656  end if
657  if (w_mse_buoyancy_enabled) then
658  call set_published_field_enabled_state(mse_fields, "w_mse_buoyancy_local", .true.)
659  allocate(w_mse_buoyancy(column_size))
660  end if
661  if (ww_mse_enabled) then
662  call set_published_field_enabled_state(mse_fields, "ww_mse_local", .true.)
663  allocate(ww_mse(column_size))
664  end if
665 
666  mse_mse_enabled=current_state%th%active
667  smse_mse_enabled=mse_mse_enabled
668  mse_mse_advection_enabled=is_component_field_available("mse_advection") .and. mse_mse_enabled
669  mse_mse_diffusion_enabled=is_component_field_available("mse_diffusion") .and. mse_mse_enabled
670  wmse_mse_enabled=current_state%w%active .and. mse_mse_enabled
671 
673 
674  if (mse_mse_enabled) then
675  call set_published_field_enabled_state(mse_fields, "mse_mse_local", .true.)
676  allocate(mse_mse(column_size))
677  end if
678  if (smse_mse_enabled) then
679  call set_published_field_enabled_state(mse_fields, "smse_mse_local", .true.)
680  allocate(smse_mse(column_size))
681  end if
682  if (mse_mse_advection_enabled) then
683  call set_published_field_enabled_state(mse_fields, "mse_mse_advection_local", .true.)
684  allocate(mse_mse_advection(column_size))
685  end if
686  if (mse_mse_diffusion_enabled) then
687  call set_published_field_enabled_state(mse_fields, "mse_mse_diffusion_local", .true.)
688  allocate(mse_mse_diffusion(column_size))
689  end if
690  if (wmse_mse_enabled) then
691  call set_published_field_enabled_state(mse_fields, "wmse_mse_local", .true.)
692  allocate(wmse_mse(column_size))
693  end if
694  end subroutine initialise_mse_diagnostics
695 
698  subroutine initialise_thetal_diagnostics(current_state)
699  type(model_state_type), target, intent(inout) :: current_state
700 
701  integer :: column_size
702  logical :: u_thetal_enabled, us_thetal_enabled, u_thetal_advection_enabled, u_thetal_viscosity_diffusion_enabled, &
703  wu_thetal_enabled, v_thetal_enabled, vs_thetal_enabled, v_thetal_advection_enabled, &
704  v_thetal_viscosity_diffusion_enabled, wv_thetal_enabled, w_thetal_enabled, ws_thetal_enabled, &
705  w_thetal_advection_enabled, w_thetal_viscosity_diffusion_enabled, w_thetal_buoyancy_enabled, ww_thetal_enabled, &
706  thetal_thetal_enabled, sthetal_thetal_enabled, thetal_thetal_advection_enabled, &
707  thetal_thetal_diffusion_enabled, wthetal_thetal_enabled
708 
709  column_size=current_state%local_grid%size(z_index)
710 
711  u_thetal_enabled=current_state%u%active .and. current_state%th%active
712  us_thetal_enabled=u_thetal_enabled
713  u_thetal_advection_enabled=is_component_field_available("u_advection") .and. &
714  is_component_field_available("th_advection") .and. u_thetal_enabled
715  u_thetal_viscosity_diffusion_enabled=is_component_field_available("u_viscosity") .and. &
716  is_component_field_available("th_diffusion") .and. u_thetal_enabled
717  wu_thetal_enabled=current_state%w%active .and. u_thetal_enabled
718 
719  some_thetal_diagnostics_enabled=u_thetal_enabled
720 
721  if (u_thetal_enabled) then
722  call set_published_field_enabled_state(thetal_fields, "u_thetal_local", .true.)
723  allocate(u_thetal(column_size))
724  end if
725  if (us_thetal_enabled) then
726  call set_published_field_enabled_state(thetal_fields, "us_thetal_local", .true.)
727  allocate(us_thetal(column_size))
728  end if
729  if (u_thetal_advection_enabled) then
730  call set_published_field_enabled_state(thetal_fields, "u_thetal_advection_local", .true.)
731  allocate(u_thetal_advection(column_size))
732  end if
733  if (u_thetal_viscosity_diffusion_enabled) then
734  call set_published_field_enabled_state(thetal_fields, "u_thetal_viscosity_diffusion_local", .true.)
735  allocate(u_thetal_viscosity_diffusion(column_size))
736  end if
737  if (wu_thetal_enabled) then
738  call set_published_field_enabled_state(thetal_fields, "wu_thetal_local", .true.)
739  allocate(wu_thetal(column_size))
740  end if
741 
742  v_thetal_enabled=current_state%v%active .and. current_state%th%active
743  vs_thetal_enabled=v_thetal_enabled
744  v_thetal_advection_enabled=is_component_field_available("v_advection") .and. &
745  is_component_field_available("th_advection") .and. v_thetal_enabled
746  v_thetal_viscosity_diffusion_enabled=is_component_field_available("v_viscosity") .and. &
747  is_component_field_available("th_diffusion") .and. v_thetal_enabled
748  wv_thetal_enabled=current_state%w%active .and. v_thetal_enabled
749 
751 
752  if (v_thetal_enabled) then
753  call set_published_field_enabled_state(thetal_fields, "v_thetal_local", .true.)
754  allocate(v_thetal(column_size))
755  end if
756  if (vs_thetal_enabled) then
757  call set_published_field_enabled_state(thetal_fields, "vs_thetal_local", .true.)
758  allocate(vs_thetal(column_size))
759  end if
760  if (v_thetal_advection_enabled) then
761  call set_published_field_enabled_state(thetal_fields, "v_thetal_advection_local", .true.)
762  allocate(v_thetal_advection(column_size))
763  end if
764  if (v_thetal_viscosity_diffusion_enabled) then
765  call set_published_field_enabled_state(thetal_fields, "v_thetal_viscosity_diffusion_local", .true.)
766  allocate(v_thetal_viscosity_diffusion(column_size))
767  end if
768  if (wv_thetal_enabled) then
769  call set_published_field_enabled_state(thetal_fields, "wv_thetal_local", .true.)
770  allocate(wv_thetal(column_size))
771  end if
772 
773  w_thetal_enabled=current_state%w%active .and. current_state%th%active
774  ws_thetal_enabled=w_thetal_enabled
775  w_thetal_advection_enabled=is_component_field_available("w_advection") .and. &
776  is_component_field_available("th_advection") .and. w_thetal_enabled
777  w_thetal_viscosity_diffusion_enabled=is_component_field_available("w_viscosity") .and. &
778  is_component_field_available("th_diffusion") .and. w_thetal_enabled
779  w_thetal_buoyancy_enabled=current_state%th%active .and. is_component_field_available("w_buoyancy")
780  ww_thetal_enabled=w_thetal_enabled
781 
783 
784  if (w_thetal_enabled) then
785  call set_published_field_enabled_state(thetal_fields, "w_thetal_local", .true.)
786  allocate(w_thetal(column_size))
787  end if
788  if (ws_thetal_enabled) then
789  call set_published_field_enabled_state(thetal_fields, "ws_thetal_local", .true.)
790  allocate(ws_thetal(column_size))
791  end if
792  if (w_thetal_advection_enabled) then
793  call set_published_field_enabled_state(thetal_fields, "w_thetal_advection_local", .true.)
794  allocate(w_thetal_advection(column_size))
795  end if
796  if (w_thetal_viscosity_diffusion_enabled) then
797  call set_published_field_enabled_state(thetal_fields, "w_thetal_viscosity_diffusion_local", .true.)
798  allocate(w_thetal_viscosity_diffusion(column_size))
799  end if
800  if (w_thetal_buoyancy_enabled) then
801  call set_published_field_enabled_state(thetal_fields, "w_thetal_buoyancy_local", .true.)
802  allocate(w_thetal_buoyancy(column_size))
803  end if
804  if (ww_thetal_enabled) then
805  call set_published_field_enabled_state(thetal_fields, "ww_thetal_local", .true.)
806  allocate(ww_thetal(column_size))
807  end if
808 
809  thetal_thetal_enabled=current_state%th%active
810  sthetal_thetal_enabled=thetal_thetal_enabled
811  thetal_thetal_advection_enabled=is_component_field_available("th_advection") .and. thetal_thetal_enabled
812  thetal_thetal_diffusion_enabled=is_component_field_available("th_diffusion") .and. thetal_thetal_enabled
813  wthetal_thetal_enabled=current_state%w%active .and. thetal_thetal_enabled
814 
816 
817  if (thetal_thetal_enabled) then
818  call set_published_field_enabled_state(thetal_fields, "thetal_thetal_local", .true.)
819  allocate(thetal_thetal(column_size))
820  end if
821  if (sthetal_thetal_enabled) then
822  call set_published_field_enabled_state(thetal_fields, "sthetal_thetal_local", .true.)
823  allocate(sthetal_thetal(column_size))
824  end if
825  if (thetal_thetal_advection_enabled) then
826  call set_published_field_enabled_state(thetal_fields, "thetal_thetal_advection_local", .true.)
827  allocate(thetal_thetal_advection(column_size))
828  end if
829  if (thetal_thetal_diffusion_enabled) then
830  call set_published_field_enabled_state(thetal_fields, "thetal_thetal_diffusion_local", .true.)
831  allocate(thetal_thetal_diffusion(column_size))
832  end if
833  if (wthetal_thetal_enabled) then
834  call set_published_field_enabled_state(thetal_fields, "wthetal_thetal_local", .true.)
835  allocate(wthetal_thetal(column_size))
836  end if
837  end subroutine initialise_thetal_diagnostics
838 
841  subroutine initialise_prognostic_budget_diagnostics(current_state)
842  type(model_state_type), target, intent(inout) :: current_state
843 
844  integer :: column_size
845  logical :: tu_su_enabled, uu_advection_enabled, uu_viscosity_enabled, wu_u_enabled, tv_sv_enabled, vv_advection_enabled, &
846  vv_viscosity_enabled, wv_v_enabled, tw_sw_enabled, ww_advection_enabled, ww_viscosity_enabled, ww_buoyancy_enabled
847 
848  tu_su_enabled=current_state%u%active
849  uu_advection_enabled=is_component_field_available("u_advection") .and. current_state%u%active
850  uu_viscosity_enabled=is_component_field_available("u_viscosity") .and. current_state%u%active
851  wu_u_enabled=current_state%u%active .and. current_state%w%active
852  tv_sv_enabled=current_state%v%active
853  vv_advection_enabled=is_component_field_available("v_advection") .and. current_state%v%active
854  vv_viscosity_enabled=is_component_field_available("v_viscosity") .and. current_state%v%active
855  wv_v_enabled=current_state%v%active .and. current_state%w%active
856  tw_sw_enabled=current_state%w%active
857  ww_advection_enabled=is_component_field_available("w_advection") .and. current_state%w%active
858  ww_viscosity_enabled=is_component_field_available("w_viscosity") .and. current_state%w%active
859  ww_buoyancy_enabled=is_component_field_available("w_buoyancy") .and. current_state%w%active
860 
861  some_prognostic_budget_diagnostics_enabled=tu_su_enabled .or. tv_sv_enabled .or. tw_sw_enabled
862 
863  column_size=current_state%local_grid%size(z_index)
864 
865  if (tu_su_enabled) then
866  call set_published_field_enabled_state(prognostic_budget_fields, "tu_su_local", .true.)
867  allocate(tu_su(column_size))
868  end if
869  if (uu_advection_enabled) then
870  call set_published_field_enabled_state(prognostic_budget_fields, "uu_advection_local", .true.)
871  allocate(uu_advection(column_size))
872  end if
873  if (uu_viscosity_enabled) then
874  call set_published_field_enabled_state(prognostic_budget_fields, "uu_viscosity_local", .true.)
875  allocate(uu_viscosity(column_size))
876  end if
877  if (wu_u_enabled) then
879  allocate(wu_u(column_size))
880  end if
881  if (tv_sv_enabled) then
882  call set_published_field_enabled_state(prognostic_budget_fields, "tv_sv_local", .true.)
883  allocate(tv_sv(column_size))
884  end if
885  if (vv_advection_enabled) then
886  call set_published_field_enabled_state(prognostic_budget_fields, "vv_advection_local", .true.)
887  allocate(vv_advection(column_size))
888  end if
889  if (vv_viscosity_enabled) then
890  call set_published_field_enabled_state(prognostic_budget_fields, "vv_viscosity_local", .true.)
891  allocate(vv_viscosity(column_size))
892  end if
893  if (wv_v_enabled) then
895  allocate(wv_v(column_size))
896  end if
897  if (tw_sw_enabled) then
898  call set_published_field_enabled_state(prognostic_budget_fields, "tw_sw_local", .true.)
899  allocate(tw_sw(column_size))
900  end if
901  if (ww_advection_enabled) then
902  call set_published_field_enabled_state(prognostic_budget_fields, "ww_advection_local", .true.)
903  allocate(ww_advection(column_size))
904  end if
905  if (ww_viscosity_enabled) then
906  call set_published_field_enabled_state(prognostic_budget_fields, "ww_viscosity_local", .true.)
907  allocate(ww_viscosity(column_size))
908  end if
909  if (ww_buoyancy_enabled) then
910  call set_published_field_enabled_state(prognostic_budget_fields, "ww_buoyancy_local", .true.)
911  allocate(ww_buoyancy(column_size))
912  end if
914 
917  subroutine initialise_uw_vw_diagnostics(current_state)
918  type(model_state_type), target, intent(inout) :: current_state
919 
920  integer :: column_size
921  logical :: uw_advection_term_enabled, vw_advection_term_enabled, uw_viscosity_term_enabled, &
922  vw_viscosity_term_enabled, uw_buoyancy_term_enabled, vw_buoyancy_term_enabled, uw_tendency_term_enabled, &
923  vw_tendency_term_enabled, uw_w_term_enabled, vw_w_term_enabled
924 
925  uw_advection_term_enabled=is_component_field_available("w_advection") .and. is_component_field_available("u_advection") &
926  .and. current_state%w%active
927  vw_advection_term_enabled=is_component_field_available("w_advection") .and. is_component_field_available("v_advection") &
928  .and. current_state%w%active
929  uw_viscosity_term_enabled=is_component_field_available("w_viscosity") .and. is_component_field_available("u_viscosity") &
930  .and. current_state%w%active
931  vw_viscosity_term_enabled=is_component_field_available("w_viscosity") .and. is_component_field_available("v_viscosity") &
932  .and. current_state%w%active
933  uw_buoyancy_term_enabled=is_component_field_available("w_buoyancy")
934  vw_buoyancy_term_enabled=is_component_field_available("w_buoyancy")
935  uw_tendency_term_enabled=current_state%w%active .and. current_state%u%active
936  vw_tendency_term_enabled=current_state%w%active .and. current_state%v%active
937  uw_w_term_enabled=current_state%w%active .and. current_state%u%active
938  vw_w_term_enabled=current_state%w%active .and. current_state%v%active
939 
940  some_uw_vw_diagnostics_enabled=uw_buoyancy_term_enabled .or. vw_buoyancy_term_enabled .or. uw_w_term_enabled .or. &
941  vw_w_term_enabled .or. uw_advection_term_enabled .or. vw_advection_term_enabled .or. uw_viscosity_term_enabled .or. &
942  vw_viscosity_term_enabled
943 
944  column_size=current_state%local_grid%size(z_index)
945 
946  if (uw_advection_term_enabled) then
947  call set_published_field_enabled_state(uw_vw_fields, "uw_advection_local", .true.)
948  allocate(uw_advection(column_size))
949  end if
950  if (vw_advection_term_enabled) then
951  call set_published_field_enabled_state(uw_vw_fields, "vw_advection_local", .true.)
952  allocate(vw_advection(column_size))
953  end if
954  if (uw_viscosity_term_enabled) then
955  call set_published_field_enabled_state(uw_vw_fields, "uw_viscosity_local", .true.)
956  allocate(uw_viscosity(column_size))
957  end if
958  if (vw_viscosity_term_enabled) then
959  call set_published_field_enabled_state(uw_vw_fields, "vw_viscosity_local", .true.)
960  allocate(vw_viscosity(column_size))
961  end if
962  if (uw_buoyancy_term_enabled) then
963  call set_published_field_enabled_state(uw_vw_fields, "uw_buoyancy_local", .true.)
964  allocate(uw_buoyancy(column_size))
965  end if
966  if (vw_buoyancy_term_enabled) then
967  call set_published_field_enabled_state(uw_vw_fields, "vw_buoyancy_local", .true.)
968  allocate(vw_buoyancy(column_size))
969  end if
970  if (uw_tendency_term_enabled) then
971  call set_published_field_enabled_state(uw_vw_fields, "uw_tendency_local", .true.)
972  allocate(uw_tendency(column_size))
973  end if
974  if (vw_tendency_term_enabled) then
975  call set_published_field_enabled_state(uw_vw_fields, "vw_tendency_local", .true.)
976  allocate(vw_tendency(column_size))
977  end if
978  if (uw_w_term_enabled) then
979  call set_published_field_enabled_state(uw_vw_fields, "uw_w_local", .true.)
980  allocate(uw_w(column_size))
981  end if
982  if (vw_w_term_enabled) then
983  call set_published_field_enabled_state(uw_vw_fields, "vw_w_local", .true.)
984  allocate(vw_w(column_size))
985  end if
986  end subroutine initialise_uw_vw_diagnostics
987 
990  subroutine initialise_q_flux_diagnostics(current_state)
991  type(model_state_type), target, intent(inout) :: current_state
992 
993  logical :: q_flux_term_enabled, q_tendency_term_enabled, q_gradient_term_enabled, q_diff_enabled, &
994  q_buoyancy_enabled
995 
996  q_flux_term_enabled=current_state%number_q_fields .gt. 0 .and. current_state%w%active
997  q_tendency_term_enabled=current_state%number_q_fields .gt. 0 .and. current_state%w%active
998  q_gradient_term_enabled=is_component_field_available("w_advection") .and. is_component_field_available("q_advection") &
999  .and. current_state%w%active .and. current_state%number_q_fields .gt. 0
1000  q_diff_enabled=is_component_field_available("q_diffusion") .and. is_component_field_available("w_viscosity") &
1001  .and. current_state%w%active .and. current_state%number_q_fields .gt. 0
1002  q_buoyancy_enabled=is_component_field_available("w_buoyancy") .and. current_state%number_q_fields .gt. 0
1003 
1004  some_q_flux_diagnostics_enabled=q_flux_term_enabled .or. q_buoyancy_enabled
1005 
1006  if (q_flux_term_enabled) then
1007  call set_published_field_enabled_state(q_flux_fields, "q_flux_transport_local", .true.)
1008  allocate(q_flux_values(current_state%local_grid%size(z_index), current_state%number_q_fields))
1009  end if
1010  if (q_tendency_term_enabled) then
1011  call set_published_field_enabled_state(q_flux_fields, "q_flux_tendency_local", .true.)
1012  allocate(q_tendency(current_state%local_grid%size(z_index), current_state%number_q_fields))
1013  end if
1014  if (q_gradient_term_enabled) then
1015  call set_published_field_enabled_state(q_flux_fields, "q_flux_gradient_local", .true.)
1016  allocate(q_gradient(current_state%local_grid%size(z_index), current_state%number_q_fields))
1017  end if
1018  if (q_diff_enabled) then
1019  call set_published_field_enabled_state(q_flux_fields, "q_flux_dissipation_local", .true.)
1020  allocate(q_diff(current_state%local_grid%size(z_index), current_state%number_q_fields))
1021  end if
1022  if (q_buoyancy_enabled) then
1023  call set_published_field_enabled_state(q_flux_fields, "q_flux_buoyancy_local", .true.)
1024  allocate(q_buoyancy(current_state%local_grid%size(z_index), current_state%number_q_fields))
1025  end if
1026  end subroutine initialise_q_flux_diagnostics
1027 
1030  subroutine initialise_theta_flux_diagnostics(current_state)
1031  type(model_state_type), target, intent(inout) :: current_state
1032 
1033  logical :: th_flux_term_enabled, th_tendency_term_enabled, th_diff_enabled, th_gradient_term_enabled, th_buoyancy_enabled
1034 
1035  th_flux_term_enabled=current_state%th%active .and. current_state%w%active
1036  th_tendency_term_enabled=current_state%th%active .and. current_state%w%active
1037  th_gradient_term_enabled=is_component_field_available("w_advection") .and. is_component_field_available("th_advection") &
1038  .and. current_state%w%active .and. current_state%th%active
1039  th_diff_enabled=is_component_field_available("th_diffusion") .and. is_component_field_available("w_viscosity") &
1040  .and. current_state%w%active .and. current_state%th%active
1041  th_buoyancy_enabled=is_component_field_available("w_buoyancy") .and. current_state%th%active
1042 
1043  some_theta_flux_diagnostics_enabled=th_flux_term_enabled .or. th_buoyancy_enabled
1044 
1045  if (th_flux_term_enabled) then
1046  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_transport_local", .true.)
1047  allocate(th_flux_values(current_state%local_grid%size(z_index)))
1048  end if
1049  if (th_tendency_term_enabled) then
1050  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_tendency_local", .true.)
1051  allocate(th_tendency(current_state%local_grid%size(z_index)))
1052  end if
1053  if (th_diff_enabled) then
1054  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_dissipation_local", .true.)
1055  allocate(th_diff(current_state%local_grid%size(z_index)))
1056  end if
1057  if (th_gradient_term_enabled) then
1058  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_gradient_local", .true.)
1059  allocate(th_gradient(current_state%local_grid%size(z_index)))
1060  end if
1061  if (th_buoyancy_enabled) then
1062  call set_published_field_enabled_state(heat_flux_fields, "heat_flux_buoyancy_local", .true.)
1063  allocate(th_buoyancy(current_state%local_grid%size(z_index)))
1064  end if
1065  end subroutine initialise_theta_flux_diagnostics
1066 
1068  subroutine clear_qt()
1069  if (allocated(us_qt)) us_qt=0.0_default_precision
1070  if (allocated(u_qt_advection)) u_qt_advection=0.0_default_precision
1071  if (allocated(u_qt_viscosity_diffusion)) u_qt_viscosity_diffusion=0.0_default_precision
1072  if (allocated(wu_qt)) wu_qt=0.0_default_precision
1073  if (allocated(vs_qt)) vs_qt=0.0_default_precision
1074  if (allocated(v_qt_advection)) v_qt_advection=0.0_default_precision
1075  if (allocated(v_qt_viscosity_diffusion)) v_qt_viscosity_diffusion=0.0_default_precision
1076  if (allocated(wv_qt)) wv_qt=0.0_default_precision
1077  if (allocated(w_qt)) w_qt=0.0_default_precision
1078  if (allocated(ws_qt)) ws_qt=0.0_default_precision
1079  if (allocated(w_qt_advection)) w_qt_advection=0.0_default_precision
1080  if (allocated(w_qt_viscosity_diffusion)) w_qt_viscosity_diffusion=0.0_default_precision
1081  if (allocated(w_qt_buoyancy)) w_qt_buoyancy=0.0_default_precision
1082  if (allocated(ww_qt)) ww_qt=0.0_default_precision
1083  if (allocated(qt_qt)) qt_qt=0.0_default_precision
1084  if (allocated(sqt_qt)) sqt_qt=0.0_default_precision
1085  if (allocated(qt_qt_advection)) qt_qt_advection=0.0_default_precision
1086  if (allocated(qt_qt_diffusion)) qt_qt_diffusion=0.0_default_precision
1087  if (allocated(wqt_qt)) wqt_qt=0.0_default_precision
1088  end subroutine clear_qt
1089 
1093  subroutine compute_qt_for_column(current_state)
1094  type(model_state_type), target, intent(inout) :: current_state
1095 
1096  real(kind=DEFAULT_PRECISION), dimension(current_state%local_grid%size(Z_INDEX)) :: upr, vpr, uprm1, vprm1, qtpr, qtprp1
1097  type(component_field_value_type) :: u_advection, u_viscosity, th_advection, th_diffusion, v_advection, v_viscosity, &
1098  w_advection, w_viscosity, w_buoyancy
1099  integer :: k
1100 
1101  if (is_component_field_available("u_advection")) u_advection=get_component_field_value(current_state, "u_advection")
1102  if (is_component_field_available("u_viscosity")) u_viscosity=get_component_field_value(current_state, "u_viscosity")
1103  if (is_component_field_available("th_advection")) th_advection=get_component_field_value(current_state, "th_advection")
1104  if (is_component_field_available("th_diffusion")) th_diffusion=get_component_field_value(current_state, "th_diffusion")
1105  if (is_component_field_available("v_advection")) v_advection=get_component_field_value(current_state, "v_advection")
1106  if (is_component_field_available("v_viscosity")) v_viscosity=get_component_field_value(current_state, "v_viscosity")
1107  if (is_component_field_available("w_advection")) w_advection=get_component_field_value(current_state, "w_advection")
1108  if (is_component_field_available("w_viscosity")) w_viscosity=get_component_field_value(current_state, "w_viscosity")
1109  if (is_component_field_available("w_buoyancy")) w_buoyancy=get_component_field_value(current_state, "w_buoyancy")
1110 
1111  do k=1, current_state%local_grid%size(z_index)
1112  upr(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x)
1113  uprm1(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x-1)
1114  if (allocated(current_state%global_grid%configuration%vertical%olubar)) then
1115  upr(k)=upr(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1116  uprm1(k)=uprm1(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1117  end if
1118  vpr(k)=current_state%v%data(k,current_state%column_local_y,current_state%column_local_x)
1119  vprm1(k)=current_state%v%data(k,current_state%column_local_y-1,current_state%column_local_x)
1120  if (allocated(current_state%global_grid%configuration%vertical%olvbar)) then
1121  vpr(k)=vpr(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1122  vprm1(k)=vprm1(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1123  end if
1124 
1125  qtpr(k)=current_state%th%data(k,current_state%column_local_y,current_state%column_local_x)
1126  qtprp1(k)=current_state%th%data(k,current_state%column_local_y,current_state%column_local_x+1)
1127  if (allocated(current_state%global_grid%configuration%vertical%olthbar)) then
1128  qtpr(k)=qtpr(k)-current_state%global_grid%configuration%vertical%olthbar(k)
1129  qtprp1(k)=qtprp1(k)-current_state%global_grid%configuration%vertical%olthbar(k)
1130  end if
1131  end do
1132  do k=2, current_state%local_grid%size(z_index)-1
1133  if (allocated(us_qt)) us_qt(k)=us_qt(k)+0.5*(upr(k)+uprm1(k))*&
1134  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*(qtpr(k)+qtprp1(k))*&
1135  current_state%su%data(k,current_state%column_local_y,current_state%column_local_x)
1136  if (allocated(u_qt_advection)) u_qt_advection(k)=u_qt_advection(k)+0.5*(upr(k)+uprm1(k))*&
1137  th_advection%real_1d_array(k)+0.5*(qtpr(k)+qtprp1(k))*u_advection%real_1d_array(k)
1139  (qtpr(k)+qtprp1(k))*u_viscosity%real_1d_array(k)+0.5*(upr(k)+uprm1(k))*th_diffusion%real_1d_array(k)
1140  if (allocated(wu_qt)) wu_qt(k)=wu_qt(k)+&
1141  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.25*(upr(k+1)+upr(k)+&
1142  uprm1(k+1)+uprm1(k))*0.5*(qtpr(k+1)+qtpr(k))
1143 
1144  if (allocated(vs_qt)) vs_qt(k)=vs_qt(k)+0.5*(vpr(k)+vprm1(k))*&
1145  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*(qtpr(k)+qtprp1(k))*&
1146  current_state%sv%data(k,current_state%column_local_y,current_state%column_local_x)
1147  if (allocated(v_qt_advection)) v_qt_advection(k)=v_qt_advection(k)+0.5*(vpr(k)+vprm1(k))*&
1148  th_advection%real_1d_array(k)+0.5*(qtpr(k)+qtprp1(k))*v_advection%real_1d_array(k)
1150  (qtpr(k)+qtprp1(k))*v_viscosity%real_1d_array(k)+0.5*(vpr(k)+vprm1(k))*th_diffusion%real_1d_array(k)
1151  if (allocated(wv_qt)) wv_qt(k)=wv_qt(k)+&
1152  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.25*(vpr(k+1)+vpr(k)+&
1153  vprm1(k+1)+vprm1(k))*0.5*(qtpr(k+1)+qtpr(k))
1154 
1155  if (allocated(w_qt)) w_qt(k)=w_qt(k)+&
1156  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(qtpr(k)+qtpr(k+1))
1157  if (allocated(ws_qt)) ws_qt(k)=ws_qt(k)+&
1158  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*&
1159  (current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+&
1160  current_state%sth%data(k+1,current_state%column_local_y,current_state%column_local_x))+0.5*(qtpr(k)+qtpr(k+1))*&
1161  current_state%sw%data(k,current_state%column_local_y,current_state%column_local_x)
1162  if (allocated(w_qt_advection)) w_qt_advection(k)=w_qt_advection(k)+&
1163  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(th_advection%real_1d_array(k)+&
1164  th_advection%real_1d_array(k+1))+0.5*(qtpr(k)+qtpr(k+1))*w_advection%real_1d_array(k)
1166  (qtpr(k)+qtpr(k+1))*w_viscosity%real_1d_array(k)+&
1167  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*&
1168  (th_diffusion%real_1d_array(k)+th_diffusion%real_1d_array(k+1))
1169  if (allocated(w_qt_buoyancy)) w_qt_buoyancy(k)=w_qt_buoyancy(k)+0.5*(qtpr(k+1)+qtpr(k))*&
1170  w_buoyancy%real_1d_array(k)
1171  if (allocated(wv_qt)) ww_qt(k)=ww_qt(k)+0.5*&
1172  (current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1173  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*0.5*(&
1174  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1175  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*qtpr(k)
1176 
1177  if (allocated(qt_qt)) qt_qt(k)=qt_qt(k)+qtpr(k)*qtpr(k)
1178  if (allocated(sqt_qt)) sqt_qt(k)=sqt_qt(k)+2.0*qtpr(k)*&
1179  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)
1180  if (allocated(qt_qt_advection)) qt_qt_advection(k)=qt_qt_advection(k)+2.0*qtpr(k)*&
1181  th_advection%real_1d_array(k)
1182  if (allocated(qt_qt_diffusion)) qt_qt_diffusion(k)=qt_qt_diffusion(k)+2.0*qtpr(k)*&
1183  th_diffusion%real_1d_array(k)
1184  if (allocated(wqt_qt)) wqt_qt(k)=wqt_qt(k)+&
1185  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(qtpr(k+1)+qtpr(k))*0.5*(&
1186  qtpr(k+1)+qtpr(k))
1187  end do
1188 
1189  if (allocated(u_advection%real_1d_array)) deallocate(u_advection%real_1d_array)
1190  if (allocated(u_viscosity%real_1d_array)) deallocate(u_viscosity%real_1d_array)
1191  if (allocated(th_advection%real_1d_array)) deallocate(th_advection%real_1d_array)
1192  if (allocated(th_diffusion%real_1d_array)) deallocate(th_diffusion%real_1d_array)
1193  if (allocated(v_advection%real_1d_array)) deallocate(v_advection%real_1d_array)
1194  if (allocated(v_viscosity%real_1d_array)) deallocate(v_viscosity%real_1d_array)
1195  if (allocated(w_advection%real_1d_array)) deallocate(w_advection%real_1d_array)
1196  if (allocated(w_viscosity%real_1d_array)) deallocate(w_viscosity%real_1d_array)
1197  if (allocated(w_buoyancy%real_1d_array)) deallocate(w_buoyancy%real_1d_array)
1198  end subroutine compute_qt_for_column
1199 
1201  subroutine clear_scalars()
1202  mflux=0.0_default_precision
1203  end subroutine clear_scalars
1204 
1207  subroutine compute_scalars_for_column(current_state)
1208  type(model_state_type), target, intent(inout) :: current_state
1209 
1210  integer :: k
1211 
1212  do k=2, current_state%local_grid%size(z_index)-1
1213  if (current_state%w%data(k, current_state%column_local_y,current_state%column_local_x) .gt. wmfcrit) then
1214  mflux=mflux+current_state%global_grid%configuration%vertical%rho(k)*&
1215  current_state%global_grid%configuration%vertical%dzn(k)*&
1216  current_state%w%data(k, current_state%column_local_y,current_state%column_local_x)
1217  end if
1218  end do
1219  end subroutine compute_scalars_for_column
1220 
1222  subroutine clear_mse()
1223  if (allocated(u_mse)) u_mse=0.0_default_precision
1224  if (allocated(us_mse)) us_mse=0.0_default_precision
1225  if (allocated(u_mse_advection)) u_mse_advection=0.0_default_precision
1226  if (allocated(u_mse_viscosity_diffusion)) u_mse_viscosity_diffusion=0.0_default_precision
1227  if (allocated(wu_mse)) wu_mse=0.0_default_precision
1228  if (allocated(v_mse)) v_mse=0.0_default_precision
1229  if (allocated(vs_mse)) vs_mse=0.0_default_precision
1230  if (allocated(v_mse_advection)) v_mse_advection=0.0_default_precision
1231  if (allocated(v_mse_viscosity_diffusion)) v_mse_viscosity_diffusion=0.0_default_precision
1232  if (allocated(wv_mse)) wv_mse=0.0_default_precision
1233  if (allocated(w_mse)) w_mse=0.0_default_precision
1234  if (allocated(ws_mse)) ws_mse=0.0_default_precision
1235  if (allocated(w_mse_advection)) w_mse_advection=0.0_default_precision
1236  if (allocated(w_mse_viscosity_diffusion)) w_mse_viscosity_diffusion=0.0_default_precision
1237  if (allocated(w_mse_buoyancy)) w_mse_buoyancy=0.0_default_precision
1238  if (allocated(ww_mse)) ww_mse=0.0_default_precision
1239  if (allocated(mse_mse)) mse_mse=0.0_default_precision
1240  if (allocated(smse_mse)) smse_mse=0.0_default_precision
1241  if (allocated(mse_mse_advection)) mse_mse_advection=0.0_default_precision
1242  if (allocated(mse_mse_diffusion)) mse_mse_diffusion=0.0_default_precision
1243  if (allocated(wmse_mse)) wmse_mse=0.0_default_precision
1244  end subroutine clear_mse
1245 
1249  subroutine compute_mse_for_column(current_state)
1250  type(model_state_type), target, intent(inout) :: current_state
1251 
1252  real(kind=DEFAULT_PRECISION), dimension(current_state%local_grid%size(Z_INDEX)) :: upr, vpr, uprm1, vprm1, msepr, mseprp1
1253  type(component_field_value_type) :: u_advection, u_viscosity, th_advection, th_diffusion, v_advection, v_viscosity, &
1254  w_advection, w_viscosity, w_buoyancy
1255  integer :: k
1256 
1257  if (is_component_field_available("u_advection")) u_advection=get_component_field_value(current_state, "u_advection")
1258  if (is_component_field_available("u_viscosity")) u_viscosity=get_component_field_value(current_state, "u_viscosity")
1259  if (is_component_field_available("th_advection")) th_advection=get_component_field_value(current_state, "th_advection")
1260  if (is_component_field_available("th_diffusion")) th_diffusion=get_component_field_value(current_state, "th_diffusion")
1261  if (is_component_field_available("v_advection")) v_advection=get_component_field_value(current_state, "v_advection")
1262  if (is_component_field_available("v_viscosity")) v_viscosity=get_component_field_value(current_state, "v_viscosity")
1263  if (is_component_field_available("w_advection")) w_advection=get_component_field_value(current_state, "w_advection")
1264  if (is_component_field_available("w_viscosity")) w_viscosity=get_component_field_value(current_state, "w_viscosity")
1265  if (is_component_field_available("w_buoyancy")) w_buoyancy=get_component_field_value(current_state, "w_buoyancy")
1266 
1267  do k=1, current_state%local_grid%size(z_index)
1268  upr(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x)
1269  uprm1(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x-1)
1270  if (allocated(current_state%global_grid%configuration%vertical%olubar)) then
1271  upr(k)=upr(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1272  uprm1(k)=uprm1(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1273  end if
1274  vpr(k)=current_state%v%data(k,current_state%column_local_y,current_state%column_local_x)
1275  vprm1(k)=current_state%v%data(k,current_state%column_local_y-1,current_state%column_local_x)
1276  if (allocated(current_state%global_grid%configuration%vertical%olvbar)) then
1277  vpr(k)=vpr(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1278  vprm1(k)=vprm1(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1279  end if
1280  msepr(k)=current_state%th%data(k,current_state%column_local_y,current_state%column_local_x)
1281  mseprp1(k)=current_state%th%data(k,current_state%column_local_y,current_state%column_local_x+1)
1282  if (allocated(current_state%global_grid%configuration%vertical%olthbar)) then
1283  msepr(k)=msepr(k)-current_state%global_grid%configuration%vertical%olthbar(k)
1284  mseprp1(k)=mseprp1(k)-current_state%global_grid%configuration%vertical%olthbar(k)
1285  end if
1286  end do
1287  do k=2, current_state%local_grid%size(z_index)-1
1288  if (allocated(u_mse)) u_mse(k)=u_mse(k)+0.5*(upr(k)+uprm1(k))*msepr(k)
1289  if (allocated(us_mse)) us_mse(k)=us_mse(k)+0.5*(upr(k)+uprm1(k))*&
1290  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*(msepr(k)+mseprp1(k))*&
1291  current_state%su%data(k,current_state%column_local_y,current_state%column_local_x)
1292  if (allocated(u_mse_advection)) u_mse_advection(k)=u_mse_advection(k)+0.5*(upr(k)+uprm1(k))*&
1293  th_advection%real_1d_array(k)+0.5*(msepr(k)+mseprp1(k))*u_advection%real_1d_array(k)
1295  (msepr(k)+mseprp1(k))*u_viscosity%real_1d_array(k)+0.5*(upr(k)+uprm1(k))*th_diffusion%real_1d_array(k)
1296  if (allocated(wu_mse)) wu_mse(k)=wu_mse(k)+&
1297  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.25*(upr(k+1)+upr(k)+&
1298  uprm1(k+1)+uprm1(k))*0.5*(msepr(k+1)+msepr(k))
1299 
1300  if (allocated(v_mse)) v_mse(k)=v_mse(k)+0.5*(vpr(k)+vprm1(k))*msepr(k)
1301  if (allocated(vs_mse)) vs_mse(k)=vs_mse(k)+0.5*(vpr(k)+vprm1(k))*&
1302  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*(msepr(k)+mseprp1(k))*&
1303  current_state%sv%data(k,current_state%column_local_y,current_state%column_local_x)
1304  if (allocated(v_mse_advection)) v_mse_advection(k)=v_mse_advection(k)+0.5*(vpr(k)+vprm1(k))*&
1305  th_advection%real_1d_array(k)+0.5*(msepr(k)+mseprp1(k))*v_advection%real_1d_array(k)
1307  (msepr(k)+mseprp1(k))*v_viscosity%real_1d_array(k)+0.5*(vpr(k)+vprm1(k))*th_diffusion%real_1d_array(k)
1308  if (allocated(wv_mse)) wv_mse(k)=wv_mse(k)+&
1309  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.25*(vpr(k+1)+vpr(k)+&
1310  vprm1(k+1)+vprm1(k))*0.5*(msepr(k+1)+msepr(k))
1311 
1312  if (allocated(w_mse)) w_mse(k)=w_mse(k)+&
1313  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(msepr(k)+msepr(k+1))
1314  if (allocated(ws_mse)) ws_mse(k)=ws_mse(k)+&
1315  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*&
1316  (current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+&
1317  current_state%sth%data(k+1,current_state%column_local_y,current_state%column_local_x))+0.5*(msepr(k)+msepr(k+1))*&
1318  current_state%sw%data(k,current_state%column_local_y,current_state%column_local_x)
1319  if (allocated(w_mse_advection)) w_mse_advection(k)=w_mse_advection(k)+&
1320  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(th_advection%real_1d_array(k)+&
1321  th_advection%real_1d_array(k+1))+0.5*(msepr(k)+msepr(k+1))*w_advection%real_1d_array(k)
1323  (msepr(k)+msepr(k+1))*w_viscosity%real_1d_array(k)+&
1324  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*&
1325  (th_diffusion%real_1d_array(k)+th_diffusion%real_1d_array(k+1))
1326  if (allocated(w_mse_buoyancy)) w_mse_buoyancy(k)=w_mse_buoyancy(k)+0.5*(msepr(k+1)+msepr(k))*&
1327  w_buoyancy%real_1d_array(k)
1328  if (allocated(wv_mse)) ww_mse(k)=ww_mse(k)+0.5*&
1329  (current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1330  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*0.5*(&
1331  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1332  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*msepr(k)
1333 
1334  if (allocated(mse_mse)) mse_mse(k)=mse_mse(k)+msepr(k)*msepr(k)
1335  if (allocated(smse_mse)) smse_mse(k)=smse_mse(k)+2.0*msepr(k)*&
1336  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)
1337  if (allocated(mse_mse_advection)) mse_mse_advection(k)=mse_mse_advection(k)+2.0*msepr(k)*&
1338  th_advection%real_1d_array(k)
1339  if (allocated(mse_mse_diffusion)) mse_mse_diffusion(k)=mse_mse_diffusion(k)+2.0*msepr(k)*&
1340  th_diffusion%real_1d_array(k)
1341  if (allocated(wmse_mse)) wmse_mse(k)=wmse_mse(k)+&
1342  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(msepr(k+1)+msepr(k))*0.5*(&
1343  msepr(k+1)+msepr(k))
1344  end do
1345 
1346  if (allocated(u_advection%real_1d_array)) deallocate(u_advection%real_1d_array)
1347  if (allocated(u_viscosity%real_1d_array)) deallocate(u_viscosity%real_1d_array)
1348  if (allocated(th_advection%real_1d_array)) deallocate(th_advection%real_1d_array)
1349  if (allocated(th_diffusion%real_1d_array)) deallocate(th_diffusion%real_1d_array)
1350  if (allocated(v_advection%real_1d_array)) deallocate(v_advection%real_1d_array)
1351  if (allocated(v_viscosity%real_1d_array)) deallocate(v_viscosity%real_1d_array)
1352  if (allocated(w_advection%real_1d_array)) deallocate(w_advection%real_1d_array)
1353  if (allocated(w_viscosity%real_1d_array)) deallocate(w_viscosity%real_1d_array)
1354  if (allocated(w_buoyancy%real_1d_array)) deallocate(w_buoyancy%real_1d_array)
1355  end subroutine compute_mse_for_column
1356 
1358  subroutine clear_thetal()
1359  if (allocated(u_thetal)) u_thetal=0.0_default_precision
1360  if (allocated(us_thetal)) us_thetal=0.0_default_precision
1361  if (allocated(u_thetal_advection)) u_thetal_advection=0.0_default_precision
1362  if (allocated(u_thetal_viscosity_diffusion)) u_thetal_viscosity_diffusion=0.0_default_precision
1363  if (allocated(wu_thetal)) wu_thetal=0.0_default_precision
1364  if (allocated(v_thetal)) v_thetal=0.0_default_precision
1365  if (allocated(vs_thetal)) vs_thetal=0.0_default_precision
1366  if (allocated(v_thetal_advection)) v_thetal_advection=0.0_default_precision
1367  if (allocated(v_thetal_viscosity_diffusion)) v_thetal_viscosity_diffusion=0.0_default_precision
1368  if (allocated(wv_thetal)) wv_thetal=0.0_default_precision
1369  if (allocated(w_thetal)) w_thetal=0.0_default_precision
1370  if (allocated(ws_thetal)) ws_thetal=0.0_default_precision
1371  if (allocated(w_thetal_advection)) w_thetal_advection=0.0_default_precision
1372  if (allocated(w_thetal_viscosity_diffusion)) w_thetal_viscosity_diffusion=0.0_default_precision
1373  if (allocated(w_thetal_buoyancy)) w_thetal_buoyancy=0.0_default_precision
1374  if (allocated(ww_thetal)) ww_thetal=0.0_default_precision
1375  if (allocated(thetal_thetal)) thetal_thetal=0.0_default_precision
1376  if (allocated(sthetal_thetal)) sthetal_thetal=0.0_default_precision
1377  if (allocated(thetal_thetal_advection)) thetal_thetal_advection=0.0_default_precision
1378  if (allocated(thetal_thetal_diffusion)) thetal_thetal_diffusion=0.0_default_precision
1379  if (allocated(wthetal_thetal)) wthetal_thetal=0.0_default_precision
1380  end subroutine clear_thetal
1381 
1384  subroutine compute_thetal_for_column(current_state)
1385  type(model_state_type), target, intent(inout) :: current_state
1386 
1387  real(kind=DEFAULT_PRECISION), dimension(current_state%local_grid%size(Z_INDEX)) :: upr, vpr, uprm1, vprm1, thlpr, thlprp1
1388  type(component_field_value_type) :: u_advection, u_viscosity, th_advection, th_diffusion, v_advection, v_viscosity, &
1389  w_advection, w_viscosity, w_buoyancy
1390  integer :: k
1391 
1392  if (is_component_field_available("u_advection")) u_advection=get_component_field_value(current_state, "u_advection")
1393  if (is_component_field_available("u_viscosity")) u_viscosity=get_component_field_value(current_state, "u_viscosity")
1394  if (is_component_field_available("th_advection")) th_advection=get_component_field_value(current_state, "th_advection")
1395  if (is_component_field_available("th_diffusion")) th_diffusion=get_component_field_value(current_state, "th_diffusion")
1396  if (is_component_field_available("v_advection")) v_advection=get_component_field_value(current_state, "v_advection")
1397  if (is_component_field_available("v_viscosity")) v_viscosity=get_component_field_value(current_state, "v_viscosity")
1398  if (is_component_field_available("w_advection")) w_advection=get_component_field_value(current_state, "w_advection")
1399  if (is_component_field_available("w_viscosity")) w_viscosity=get_component_field_value(current_state, "w_viscosity")
1400  if (is_component_field_available("w_buoyancy")) w_buoyancy=get_component_field_value(current_state, "w_buoyancy")
1401 
1402  do k=1, current_state%local_grid%size(z_index)
1403  upr(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x)
1404  uprm1(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x-1)
1405  if (allocated(current_state%global_grid%configuration%vertical%olubar)) then
1406  upr(k)=upr(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1407  uprm1(k)=uprm1(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1408  end if
1409  vpr(k)=current_state%v%data(k,current_state%column_local_y,current_state%column_local_x)
1410  vprm1(k)=current_state%v%data(k,current_state%column_local_y-1,current_state%column_local_x)
1411  if (allocated(current_state%global_grid%configuration%vertical%olvbar)) then
1412  vpr(k)=vpr(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1413  vprm1(k)=vprm1(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1414  end if
1415  thlpr(k)=current_state%th%data(k,current_state%column_local_y,current_state%column_local_x)
1416  thlprp1(k)=current_state%th%data(k,current_state%column_local_y,current_state%column_local_x+1)
1417  if (allocated(current_state%global_grid%configuration%vertical%olthbar)) then
1418  thlpr(k)=thlpr(k)-current_state%global_grid%configuration%vertical%olthbar(k)
1419  thlprp1(k)=thlprp1(k)-current_state%global_grid%configuration%vertical%olthbar(k)
1420  end if
1421  end do
1422  do k=2, current_state%local_grid%size(z_index)-1
1423  if (allocated(u_thetal)) u_thetal(k)=u_thetal(k)+0.5*(upr(k)+uprm1(k))*thlpr(k)
1424  if (allocated(us_thetal)) us_thetal(k)=us_thetal(k)+0.5*(upr(k)+uprm1(k))*&
1425  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*(thlpr(k)+thlprp1(k))*&
1426  current_state%su%data(k,current_state%column_local_y,current_state%column_local_x)
1427  if (allocated(u_thetal_advection)) u_thetal_advection(k)=u_thetal_advection(k)+0.5*(upr(k)+uprm1(k))*&
1428  th_advection%real_1d_array(k)+0.5*(thlpr(k)+thlprp1(k))*u_advection%real_1d_array(k)
1430  (thlpr(k)+thlprp1(k))*u_viscosity%real_1d_array(k)+0.5*(upr(k)+uprm1(k))*th_diffusion%real_1d_array(k)
1431  if (allocated(wu_thetal)) wu_thetal(k)=wu_thetal(k)+&
1432  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.25*(upr(k+1)+upr(k)+&
1433  uprm1(k+1)+uprm1(k))*0.5*(thlpr(k+1)+thlpr(k))
1434 
1435  if (allocated(v_thetal)) v_thetal(k)=v_thetal(k)+0.5*(vpr(k)+vprm1(k))*thlpr(k)
1436  if (allocated(vs_thetal)) vs_thetal(k)=vs_thetal(k)+0.5*(vpr(k)+vprm1(k))*&
1437  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*(thlpr(k)+thlprp1(k))*&
1438  current_state%sv%data(k,current_state%column_local_y,current_state%column_local_x)
1439  if (allocated(v_thetal_advection)) v_thetal_advection(k)=v_thetal_advection(k)+0.5*(vpr(k)+vprm1(k))*&
1440  th_advection%real_1d_array(k)+0.5*(thlpr(k)+thlprp1(k))*v_advection%real_1d_array(k)
1442  (thlpr(k)+thlprp1(k))*v_viscosity%real_1d_array(k)+0.5*(vpr(k)+vprm1(k))*th_diffusion%real_1d_array(k)
1443  if (allocated(wv_thetal)) wv_thetal(k)=wv_thetal(k)+&
1444  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.25*(vpr(k+1)+vpr(k)+&
1445  vprm1(k+1)+vprm1(k))*0.5*(thlpr(k+1)+thlpr(k))
1446 
1447  if (allocated(w_thetal)) w_thetal(k)=w_thetal(k)+&
1448  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(thlpr(k)+thlpr(k+1))
1449  if (allocated(ws_thetal)) ws_thetal(k)=ws_thetal(k)+&
1450  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*&
1451  (current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+&
1452  current_state%sth%data(k+1,current_state%column_local_y,current_state%column_local_x))+0.5*(thlpr(k)+thlpr(k+1))*&
1453  current_state%sw%data(k,current_state%column_local_y,current_state%column_local_x)
1455  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(th_advection%real_1d_array(k)+&
1456  th_advection%real_1d_array(k+1))+0.5*(thlpr(k)+thlpr(k+1))*w_advection%real_1d_array(k)
1458  (thlpr(k)+thlpr(k+1))*w_viscosity%real_1d_array(k)+&
1459  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*&
1460  (th_diffusion%real_1d_array(k)+th_diffusion%real_1d_array(k+1))
1461  if (allocated(w_thetal_buoyancy)) w_thetal_buoyancy(k)=w_thetal_buoyancy(k)+0.5*(thlpr(k+1)+thlpr(k))*&
1462  w_buoyancy%real_1d_array(k)
1463  if (allocated(wv_thetal)) ww_thetal(k)=ww_thetal(k)+0.5*&
1464  (current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1465  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*0.5*(&
1466  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1467  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*thlpr(k)
1468 
1469  if (allocated(thetal_thetal)) thetal_thetal(k)=thetal_thetal(k)+thlpr(k)*thlpr(k)
1470  if (allocated(sthetal_thetal)) sthetal_thetal(k)=sthetal_thetal(k)+2.0*thlpr(k)*&
1471  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)
1472  if (allocated(thetal_thetal_advection)) thetal_thetal_advection(k)=thetal_thetal_advection(k)+2.0*thlpr(k)*&
1473  th_advection%real_1d_array(k)
1474  if (allocated(thetal_thetal_diffusion)) thetal_thetal_diffusion(k)=thetal_thetal_diffusion(k)+2.0*thlpr(k)*&
1475  th_diffusion%real_1d_array(k)
1476  if (allocated(wthetal_thetal)) wthetal_thetal(k)=wthetal_thetal(k)+&
1477  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(thlpr(k+1)+thlpr(k))*0.5*(&
1478  thlpr(k+1)+thlpr(k))
1479  end do
1480 
1481  if (allocated(u_advection%real_1d_array)) deallocate(u_advection%real_1d_array)
1482  if (allocated(u_viscosity%real_1d_array)) deallocate(u_viscosity%real_1d_array)
1483  if (allocated(th_advection%real_1d_array)) deallocate(th_advection%real_1d_array)
1484  if (allocated(th_diffusion%real_1d_array)) deallocate(th_diffusion%real_1d_array)
1485  if (allocated(v_advection%real_1d_array)) deallocate(v_advection%real_1d_array)
1486  if (allocated(v_viscosity%real_1d_array)) deallocate(v_viscosity%real_1d_array)
1487  if (allocated(w_advection%real_1d_array)) deallocate(w_advection%real_1d_array)
1488  if (allocated(w_viscosity%real_1d_array)) deallocate(w_viscosity%real_1d_array)
1489  if (allocated(w_buoyancy%real_1d_array)) deallocate(w_buoyancy%real_1d_array)
1490  end subroutine compute_thetal_for_column
1491 
1493  subroutine clear_prognostic_budgets()
1494  if (allocated(tu_su)) tu_su=0.0_default_precision
1495  if (allocated(uu_advection)) uu_advection=0.0_default_precision
1496  if (allocated(uu_viscosity)) uu_viscosity=0.0_default_precision
1497  if (allocated(wu_u)) wu_u=0.0_default_precision
1498  if (allocated(tv_sv)) tv_sv=0.0_default_precision
1499  if (allocated(vv_advection)) vv_advection=0.0_default_precision
1500  if (allocated(vv_viscosity)) vv_viscosity=0.0_default_precision
1501  if (allocated(wv_v)) wv_v=0.0_default_precision
1502  if (allocated(tw_sw)) tw_sw=0.0_default_precision
1503  if (allocated(ww_advection)) ww_advection=0.0_default_precision
1504  if (allocated(ww_viscosity)) ww_viscosity=0.0_default_precision
1505  if (allocated(ww_buoyancy)) ww_buoyancy=0.0_default_precision
1506  end subroutine clear_prognostic_budgets
1507 
1510  subroutine compute_prognostic_budgets_for_column(current_state)
1511  type(model_state_type), target, intent(inout) :: current_state
1512 
1513  real(kind=DEFAULT_PRECISION), dimension(current_state%local_grid%size(Z_INDEX)) :: upr, vpr, uprm1, vprm1
1514  type(component_field_value_type) :: u_advection, u_viscosity, v_advection, v_viscosity, w_advection, w_viscosity, w_buoyancy
1515  integer :: k
1516 
1517  if (is_component_field_available("u_advection")) u_advection=get_component_field_value(current_state, "u_advection")
1518  if (is_component_field_available("u_viscosity")) u_viscosity=get_component_field_value(current_state, "u_viscosity")
1519  if (is_component_field_available("v_advection")) v_advection=get_component_field_value(current_state, "v_advection")
1520  if (is_component_field_available("v_viscosity")) v_viscosity=get_component_field_value(current_state, "v_viscosity")
1521  if (is_component_field_available("w_advection")) w_advection=get_component_field_value(current_state, "w_advection")
1522  if (is_component_field_available("w_viscosity")) w_viscosity=get_component_field_value(current_state, "w_viscosity")
1523  if (is_component_field_available("w_buoyancy")) w_buoyancy=get_component_field_value(current_state, "w_buoyancy")
1524 
1525  do k=1, current_state%local_grid%size(z_index)
1526  upr(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x)
1527  uprm1(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x-1)
1528  if (allocated(current_state%global_grid%configuration%vertical%olubar)) then
1529  upr(k)=upr(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1530  uprm1(k)=uprm1(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1531  end if
1532  vpr(k)=current_state%v%data(k,current_state%column_local_y,current_state%column_local_x)
1533  vprm1(k)=current_state%v%data(k,current_state%column_local_y-1,current_state%column_local_x)
1534  if (allocated(current_state%global_grid%configuration%vertical%olvbar)) then
1535  vpr(k)=vpr(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1536  vprm1(k)=vprm1(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1537  end if
1538  end do
1539  do k=2, current_state%local_grid%size(z_index)-1
1540  if (allocated(tu_su)) tu_su(k)=tu_su(k)+2.0*upr(k)*current_state%su%data(k,current_state%column_local_y,&
1541  current_state%column_local_x)
1542  if (allocated(uu_advection)) uu_advection(k)=uu_advection(k)+2.0*upr(k)*u_advection%real_1d_array(k)
1543  if (allocated(uu_viscosity)) uu_viscosity(k)=uu_viscosity(k)+2.0*upr(k)*u_viscosity%real_1d_array(k)
1544  if (allocated(wu_u)) wu_u(k)=wu_u(k)+0.25*(upr(k)+upr(k+1)+uprm1(k)+uprm1(k+1))*0.25*&
1545  (upr(k)+upr(k+1)+uprm1(k)+uprm1(k+1))*current_state%w%data(k,current_state%column_local_y,&
1546  current_state%column_local_x)
1547  if (allocated(tv_sv)) tv_sv(k)=tv_sv(k)+2.0*vpr(k)*current_state%sv%data(k,current_state%column_local_y,&
1548  current_state%column_local_x)
1549  if (allocated(vv_advection)) vv_advection(k)=vv_advection(k)+2.0*vpr(k)*v_advection%real_1d_array(k)
1550  if (allocated(vv_viscosity)) uu_viscosity(k)=vv_viscosity(k)+2.0*vpr(k)*v_viscosity%real_1d_array(k)
1551  if (allocated(wv_v)) wv_v(k)=wv_v(k)+0.25*(vpr(k)+vpr(k+1)+vprm1(k)+vprm1(k+1))*0.25*&
1552  (vpr(k)+vpr(k+1)+vprm1(k)+vprm1(k+1))*current_state%w%data(k,current_state%column_local_y,&
1553  current_state%column_local_x)
1554  if (allocated(tw_sw)) tw_sw(k)=tw_sw(k)+2.0*current_state%w%data(k,current_state%column_local_y,&
1555  current_state%column_local_x)*current_state%sw%data(k,current_state%column_local_y,&
1556  current_state%column_local_x)
1557  if (allocated(ww_advection)) ww_advection(k)=ww_advection(k)+2.0*current_state%w%data(k,current_state%column_local_y,&
1558  current_state%column_local_x)*w_advection%real_1d_array(k)
1559  if (allocated(ww_viscosity)) ww_viscosity(k)=ww_viscosity(k)+2.0*current_state%w%data(k,current_state%column_local_y,&
1560  current_state%column_local_x)*w_viscosity%real_1d_array(k)
1561  if (allocated(ww_buoyancy)) ww_buoyancy(k)=ww_buoyancy(k)+2.0*current_state%w%data(k,current_state%column_local_y,&
1562  current_state%column_local_x)*w_buoyancy%real_1d_array(k)
1563  end do
1564 
1565  if (allocated(u_advection%real_1d_array)) deallocate(u_advection%real_1d_array)
1566  if (allocated(u_viscosity%real_1d_array)) deallocate(u_viscosity%real_1d_array)
1567  if (allocated(v_advection%real_1d_array)) deallocate(v_advection%real_1d_array)
1568  if (allocated(v_viscosity%real_1d_array)) deallocate(v_viscosity%real_1d_array)
1569  if (allocated(w_advection%real_1d_array)) deallocate(w_advection%real_1d_array)
1570  if (allocated(w_viscosity%real_1d_array)) deallocate(w_viscosity%real_1d_array)
1571  if (allocated(w_buoyancy%real_1d_array)) deallocate(w_buoyancy%real_1d_array)
1573 
1574 
1576  subroutine clear_uw_vw()
1577  if (allocated(uw_advection)) uw_advection=0.0_default_precision
1578  if (allocated(vw_advection)) vw_advection=0.0_default_precision
1579  if (allocated(uw_viscosity)) uw_viscosity=0.0_default_precision
1580  if (allocated(vw_viscosity)) vw_viscosity=0.0_default_precision
1581  if (allocated(uw_buoyancy)) uw_buoyancy=0.0_default_precision
1582  if (allocated(vw_buoyancy)) vw_buoyancy=0.0_default_precision
1583  if (allocated(uw_tendency)) uw_tendency=0.0_default_precision
1584  if (allocated(vw_tendency)) vw_tendency=0.0_default_precision
1585  if (allocated(uw_w)) uw_w=0.0_default_precision
1586  if (allocated(vw_w)) vw_w=0.0_default_precision
1587  end subroutine clear_uw_vw
1588 
1591  subroutine compute_uw_vw_for_column(current_state)
1592  type(model_state_type), target, intent(inout) :: current_state
1593 
1594  real(kind=DEFAULT_PRECISION), dimension(current_state%local_grid%size(Z_INDEX)) :: upr, vpr, uprm1, vprm1
1595  type(component_field_value_type) :: w_advection, v_advection, u_advection, w_viscosity, v_viscosity, u_viscosity, &
1596  w_buoyancy
1597  integer :: k
1598 
1599  if (is_component_field_available("w_advection")) w_advection=get_component_field_value(current_state, "w_advection")
1600  if (is_component_field_available("v_advection")) v_advection=get_component_field_value(current_state, "v_advection")
1601  if (is_component_field_available("u_advection")) u_advection=get_component_field_value(current_state, "u_advection")
1602  if (is_component_field_available("w_viscosity")) w_viscosity=get_component_field_value(current_state, "w_viscosity")
1603  if (is_component_field_available("v_viscosity")) v_viscosity=get_component_field_value(current_state, "v_viscosity")
1604  if (is_component_field_available("u_viscosity")) u_viscosity=get_component_field_value(current_state, "u_viscosity")
1605  if (is_component_field_available("w_buoyancy")) w_buoyancy=get_component_field_value(current_state, "w_buoyancy")
1606 
1607  do k=1, current_state%local_grid%size(z_index)
1608  upr(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x)
1609  uprm1(k)=current_state%u%data(k,current_state%column_local_y,current_state%column_local_x-1)
1610  if (allocated(current_state%global_grid%configuration%vertical%olubar)) then
1611  upr(k)=upr(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1612  uprm1(k)=uprm1(k)-(current_state%global_grid%configuration%vertical%olubar(k)-current_state%ugal)
1613  end if
1614  vpr(k)=current_state%v%data(k,current_state%column_local_y,current_state%column_local_x)
1615  vprm1(k)=current_state%v%data(k,current_state%column_local_y-1,current_state%column_local_x)
1616  if (allocated(current_state%global_grid%configuration%vertical%olvbar)) then
1617  vpr(k)=vpr(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1618  vprm1(k)=vprm1(k)-(current_state%global_grid%configuration%vertical%olvbar(k)-current_state%vgal)
1619  end if
1620  end do
1621  do k=2, current_state%local_grid%size(z_index)-1
1622  if (allocated(uw_advection)) uw_advection(k)=uw_advection(k)+0.5*(upr(k)+uprm1(k))*0.5*&
1623  (w_advection%real_1d_array(k)+w_advection%real_1d_array(k-1))+0.25*(&
1624  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1625  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x)+&
1626  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x+1)+&
1627  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x+1))*u_advection%real_1d_array(k)
1628  if (allocated(vw_advection)) vw_advection(k)=vw_advection(k)+0.5*(vpr(k)+vprm1(k))*0.5*&
1629  (w_advection%real_1d_array(k)+w_advection%real_1d_array(k-1))+0.25*(&
1630  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1631  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x)+&
1632  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x+1)+&
1633  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x+1))*v_advection%real_1d_array(k)
1634  if (allocated(uw_viscosity)) uw_viscosity(k)=uw_viscosity(k)+0.5*(upr(k)+uprm1(k))*0.5*&
1635  (w_viscosity%real_1d_array(k)+w_viscosity%real_1d_array(k-1))+0.25*(&
1636  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1637  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x)+&
1638  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x+1)+&
1639  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x+1))*u_viscosity%real_1d_array(k)
1640  if (allocated(vw_viscosity)) vw_viscosity(k)=vw_viscosity(k)+0.5*(vpr(k)+vprm1(k))*0.5*&
1641  (w_viscosity%real_1d_array(k)+w_viscosity%real_1d_array(k-1))+0.25*(&
1642  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1643  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x)+&
1644  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x+1)+&
1645  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x+1))*v_viscosity%real_1d_array(k)
1646  if (allocated(uw_buoyancy)) uw_buoyancy(k)=uw_buoyancy(k)+0.5*(upr(k)+uprm1(k))*0.5*(&
1647  w_buoyancy%real_1d_array(k)+w_buoyancy%real_1d_array(k-1))
1648  if (allocated(vw_buoyancy)) vw_buoyancy(k)=vw_buoyancy(k)+0.5*(vpr(k)+vprm1(k))*0.5*(&
1649  w_buoyancy%real_1d_array(k)+w_buoyancy%real_1d_array(k-1))
1650  if (allocated(uw_tendency)) uw_tendency(k)=uw_tendency(k)+0.25*(&
1651  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1652  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x)+&
1653  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x+1)+&
1654  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x+1))*&
1655  current_state%su%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*(&
1656  current_state%sw%data(k,current_state%column_local_y,current_state%column_local_x)+&
1657  current_state%sw%data(k-1,current_state%column_local_y,current_state%column_local_x))*0.5*(upr(k)+uprm1(k))
1658  if (allocated(vw_tendency)) vw_tendency(k)=vw_tendency(k)+0.25*(&
1659  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1660  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x)+&
1661  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x+1)+&
1662  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x+1))*&
1663  current_state%sv%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*(&
1664  current_state%sw%data(k,current_state%column_local_y,current_state%column_local_x)+&
1665  current_state%sw%data(k-1,current_state%column_local_y,current_state%column_local_x))*0.5*(vpr(k)+vprm1(k))
1666  if (allocated(uw_w)) uw_w(k)=uw_w(k)+0.25*(upr(k)+upr(k+1)+uprm1(k)+uprm1(k+1))*&
1667  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*&
1668  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)
1669  if (allocated(vw_w)) vw_w(k)=vw_w(k)+0.25*(vpr(k)+vpr(k+1)+vprm1(k)+vprm1(k+1))*&
1670  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*&
1671  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)
1672  end do
1673 
1674  if (allocated(u_advection%real_1d_array)) deallocate(u_advection%real_1d_array)
1675  if (allocated(u_viscosity%real_1d_array)) deallocate(u_viscosity%real_1d_array)
1676  if (allocated(v_advection%real_1d_array)) deallocate(v_advection%real_1d_array)
1677  if (allocated(v_viscosity%real_1d_array)) deallocate(v_viscosity%real_1d_array)
1678  if (allocated(w_advection%real_1d_array)) deallocate(w_advection%real_1d_array)
1679  if (allocated(w_viscosity%real_1d_array)) deallocate(w_viscosity%real_1d_array)
1680  if (allocated(w_buoyancy%real_1d_array)) deallocate(w_buoyancy%real_1d_array)
1681  end subroutine compute_uw_vw_for_column
1682 
1684  subroutine clear_q_fluxes()
1685  if (allocated(q_flux_values)) q_flux_values=0.0_default_precision
1686  if (allocated(q_gradient)) q_gradient=0.0_default_precision
1687  if (allocated(q_diff)) q_diff=0.0_default_precision
1688  if (allocated(q_buoyancy)) q_buoyancy=0.0_default_precision
1689  if (allocated(q_tendency)) q_tendency=0.0_default_precision
1690  end subroutine clear_q_fluxes
1691 
1694  subroutine compute_q_flux_for_column(current_state)
1695  type(model_state_type), target, intent(inout) :: current_state
1696 
1697  integer :: k, n
1698  real(kind=DEFAULT_PRECISION), dimension(current_state%local_grid%size(Z_INDEX)) :: qpr
1699  type(component_field_value_type) :: w_advection_published_value, q_advection_published_value, w_viscosity_published_value, &
1700  q_diffusion_published_value, w_buoyancy_published_value
1701 
1702  if (allocated(q_gradient)) then
1703  w_advection_published_value=get_component_field_value(current_state, "w_advection")
1704  q_advection_published_value=get_component_field_value(current_state, "q_advection")
1705  end if
1706  if (allocated(q_diff)) then
1707  w_viscosity_published_value=get_component_field_value(current_state, "w_viscosity")
1708  q_diffusion_published_value=get_component_field_value(current_state, "q_diffusion")
1709  end if
1710  if (allocated(q_buoyancy)) then
1711  w_buoyancy_published_value=get_component_field_value(current_state, "w_buoyancy")
1712  end if
1713 
1714  do n=1, current_state%number_q_fields
1715  do k=1, current_state%local_grid%size(z_index)
1716  qpr(k)=current_state%q(n)%data(k,current_state%column_local_y,current_state%column_local_x)
1717  if (allocated(current_state%global_grid%configuration%vertical%olqbar)) then
1718  qpr(k)=qpr(k)-current_state%global_grid%configuration%vertical%olqbar(k,n)
1719  end if
1720  end do
1721  do k=2, current_state%local_grid%size(z_index)-1
1722  if (allocated(q_flux_values)) q_flux_values(k,n)=q_flux_values(k,n)+&
1723  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*&
1724  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(qpr(k)+qpr(k+1))
1725  if (allocated(q_tendency)) q_tendency(k,n)=q_tendency(k,n)+0.5*&
1726  (current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1727  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*&
1728  current_state%sq(n)%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*&
1729  qpr(k)*(current_state%sw%data(k,current_state%column_local_y,current_state%column_local_x)+&
1730  current_state%sw%data(k-1,current_state%column_local_y,current_state%column_local_x))
1731  if (allocated(q_gradient)) then
1732  q_gradient(k,n)=q_gradient(k,n)+qpr(k)*0.5*(w_advection_published_value%real_1d_array(k)+&
1733  w_advection_published_value%real_1d_array(k-1))+0.5*&
1734  (current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1735  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*&
1736  q_advection_published_value%real_2d_array(k, n)
1737  end if
1738  if (allocated(q_diff)) then
1739  q_diff(k,n)=q_diff(k,n)+qpr(k)*0.5*(w_viscosity_published_value%real_1d_array(k)+&
1740  w_viscosity_published_value%real_1d_array(k-1))+&
1741  0.5*(current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1742  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*&
1743  q_diffusion_published_value%real_2d_array(k,n)
1744  end if
1745  if (allocated(q_buoyancy)) then
1746  q_buoyancy(k,n)=q_buoyancy(k,n)+qpr(k)*0.5*(w_buoyancy_published_value%real_1d_array(k)+&
1747  w_buoyancy_published_value%real_1d_array(k-1))
1748  end if
1749  end do
1750  end do
1751  if (allocated(w_advection_published_value%real_1d_array)) deallocate(w_advection_published_value%real_1d_array)
1752  if (allocated(q_advection_published_value%real_2d_array)) deallocate(q_advection_published_value%real_2d_array)
1753  if (allocated(w_viscosity_published_value%real_1d_array)) deallocate(w_viscosity_published_value%real_1d_array)
1754  if (allocated(q_diffusion_published_value%real_2d_array)) deallocate(q_diffusion_published_value%real_2d_array)
1755  if (allocated(w_buoyancy_published_value%real_1d_array)) deallocate(w_buoyancy_published_value%real_1d_array)
1756  end subroutine compute_q_flux_for_column
1757 
1759  subroutine clear_theta_fluxes()
1760  if (allocated(th_flux_values)) th_flux_values=0.0_default_precision
1761  if (allocated(th_tendency)) th_tendency=0.0_default_precision
1762  if (allocated(th_gradient)) th_gradient=0.0_default_precision
1763  if (allocated(th_diff)) th_diff=0.0_default_precision
1764  if (allocated(th_buoyancy)) th_buoyancy=0.0_default_precision
1765  end subroutine clear_theta_fluxes
1766 
1769  subroutine compute_theta_flux_for_column(current_state)
1770  type(model_state_type), target, intent(inout) :: current_state
1771 
1772  integer :: k
1773  real(kind=DEFAULT_PRECISION), dimension(current_state%local_grid%size(Z_INDEX)) :: thpr
1774  type(component_field_value_type) :: w_advection_published_value, th_advection_published_value, w_viscosity_published_value, &
1775  th_diffusion_published_value, w_buoyancy_published_value
1776 
1777  do k=1, current_state%local_grid%size(z_index)
1778  thpr(k)=current_state%th%data(k,current_state%column_local_y,current_state%column_local_x)
1779  if (allocated(current_state%global_grid%configuration%vertical%olthbar)) then
1780  thpr(k)=thpr(k)-current_state%global_grid%configuration%vertical%olthbar(k)
1781  end if
1782  end do
1783  if (allocated(th_gradient)) then
1784  w_advection_published_value=get_component_field_value(current_state, "w_advection")
1785  th_advection_published_value=get_component_field_value(current_state, "th_advection")
1786  end if
1787  if (allocated(th_diff)) then
1788  w_viscosity_published_value=get_component_field_value(current_state, "w_viscosity")
1789  th_diffusion_published_value=get_component_field_value(current_state, "th_diffusion")
1790  end if
1791  if (allocated(th_buoyancy)) then
1792  w_buoyancy_published_value=get_component_field_value(current_state, "w_buoyancy")
1793  end if
1794  do k=2, current_state%local_grid%size(z_index)-1
1795  if (allocated(th_flux_values)) th_flux_values(k)=th_flux_values(k)+&
1796  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*&
1797  current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)*0.5*(thpr(k)+thpr(k+1))
1798  if (allocated(th_tendency)) th_tendency(k)=th_tendency(k)+0.5*&
1799  (current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1800  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*&
1801  current_state%sth%data(k,current_state%column_local_y,current_state%column_local_x)+0.5*&
1802  thpr(k)*(current_state%sw%data(k,current_state%column_local_y,current_state%column_local_x)+&
1803  current_state%sw%data(k-1,current_state%column_local_y,current_state%column_local_x))
1804  if (allocated(th_gradient)) then
1805  th_gradient(k)=th_gradient(k)+thpr(k)*0.5*(w_advection_published_value%real_1d_array(k)+&
1806  w_advection_published_value%real_1d_array(k-1))+0.5*&
1807  (current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1808  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*&
1809  th_advection_published_value%real_1d_array(k)
1810  end if
1811  if (allocated(th_diff)) then
1812  th_diff(k)=th_diff(k)+thpr(k)*0.5*(w_viscosity_published_value%real_1d_array(k)+&
1813  w_viscosity_published_value%real_1d_array(k-1))+&
1814  0.5*(current_state%w%data(k,current_state%column_local_y,current_state%column_local_x)+&
1815  current_state%w%data(k-1,current_state%column_local_y,current_state%column_local_x))*&
1816  th_diffusion_published_value%real_1d_array(k)
1817  end if
1818  if (allocated(th_buoyancy)) then
1819  th_buoyancy(k)=th_buoyancy(k)+thpr(k)*0.5*(w_buoyancy_published_value%real_1d_array(k)+&
1820  w_buoyancy_published_value%real_1d_array(k-1))
1821  end if
1822  end do
1823  if (allocated(w_advection_published_value%real_1d_array)) deallocate(w_advection_published_value%real_1d_array)
1824  if (allocated(th_advection_published_value%real_1d_array)) deallocate(th_advection_published_value%real_1d_array)
1825  if (allocated(w_viscosity_published_value%real_1d_array)) deallocate(w_viscosity_published_value%real_1d_array)
1826  if (allocated(th_diffusion_published_value%real_1d_array)) deallocate(th_diffusion_published_value%real_1d_array)
1827  if (allocated(w_buoyancy_published_value%real_1d_array)) deallocate(w_buoyancy_published_value%real_1d_array)
1828  end subroutine compute_theta_flux_for_column
1829 
1833  logical function is_field_heat_flux(name)
1834  character(len=*), intent(in) :: name
1835 
1836  is_field_heat_flux=c_contains(heat_flux_fields, name)
1837  end function is_field_heat_flux
1838 
1842  logical function is_field_q_flux(name)
1843  character(len=*), intent(in) :: name
1844 
1845  is_field_q_flux=c_contains(q_flux_fields, name)
1846  end function is_field_q_flux
1847 
1851  logical function is_field_uw_vw(name)
1852  character(len=*), intent(in) :: name
1853 
1854  is_field_uw_vw=c_contains(uw_vw_fields, name)
1855  end function is_field_uw_vw
1856 
1860  logical function is_field_prognostic_budget(name)
1861  character(len=*), intent(in) :: name
1862 
1864  end function is_field_prognostic_budget
1865 
1869  logical function is_field_thetal(name)
1870  character(len=*), intent(in) :: name
1871 
1872  is_field_thetal=c_contains(thetal_fields, name)
1873  end function is_field_thetal
1874 
1878  logical function is_field_mse(name)
1879  character(len=*), intent(in) :: name
1880 
1881  is_field_mse=c_contains(mse_fields, name)
1882  end function is_field_mse
1883 
1887  logical function is_field_qt(name)
1888  character(len=*), intent(in) :: name
1889 
1890  is_field_qt=c_contains(qt_fields, name)
1891  end function is_field_qt
1892 
1896  logical function is_field_scalar(name)
1897  character(len=*), intent(in) :: name
1898 
1899  is_field_scalar=c_contains(scalar_fields, name)
1900  end function is_field_scalar
1901 
1906  subroutine field_value_retrieval_callback(current_state, name, field_value)
1907  type(model_state_type), target, intent(inout) :: current_state
1908  character(len=*), intent(in) :: name
1909  type(component_field_value_type), intent(out) :: field_value
1910 
1911  if (name .eq. "heat_flux_transport_local" .and. allocated(th_flux_values)) then
1912  call set_published_field_value(field_value, real_1d_field=th_flux_values)
1913  else if (name .eq. "heat_flux_gradient_local" .and. allocated(th_gradient)) then
1914  call set_published_field_value(field_value, real_1d_field=th_gradient)
1915  else if (name .eq. "heat_flux_dissipation_local" .and. allocated(th_diff)) then
1916  call set_published_field_value(field_value, real_1d_field=th_diff)
1917  else if (name .eq. "heat_flux_buoyancy_local" .and. allocated(th_buoyancy)) then
1918  call set_published_field_value(field_value, real_1d_field=th_buoyancy)
1919  else if (name .eq. "heat_flux_tendency_local" .and. allocated(th_tendency)) then
1920  call set_published_field_value(field_value, real_1d_field=th_tendency)
1921  else if (name .eq. "q_flux_transport_local" .and. allocated(q_flux_values)) then
1922  call set_published_field_value(field_value, real_2d_field=q_flux_values)
1923  else if (name .eq. "q_flux_gradient_local" .and. allocated(q_gradient)) then
1924  call set_published_field_value(field_value, real_2d_field=q_gradient)
1925  else if (name .eq. "q_flux_dissipation_local" .and. allocated(q_diff)) then
1926  call set_published_field_value(field_value, real_2d_field=q_diff)
1927  else if (name .eq. "q_flux_buoyancy_local" .and. allocated(q_buoyancy)) then
1928  call set_published_field_value(field_value, real_2d_field=q_buoyancy)
1929  else if (name .eq. "q_flux_tendency_local" .and. allocated(q_tendency)) then
1930  call set_published_field_value(field_value, real_2d_field=q_tendency)
1931  else if (name .eq. "uw_advection_local" .and. allocated(uw_advection)) then
1932  call set_published_field_value(field_value, real_1d_field=uw_advection)
1933  else if (name .eq. "vw_advection_local" .and. allocated(vw_advection)) then
1934  call set_published_field_value(field_value, real_1d_field=vw_advection)
1935  else if (name .eq. "uw_viscosity_local" .and. allocated(uw_viscosity)) then
1936  call set_published_field_value(field_value, real_1d_field=uw_viscosity)
1937  else if (name .eq. "vw_viscosity_local" .and. allocated(vw_viscosity)) then
1938  call set_published_field_value(field_value, real_1d_field=vw_viscosity)
1939  else if (name .eq. "uw_buoyancy_local" .and. allocated(uw_buoyancy)) then
1940  call set_published_field_value(field_value, real_1d_field=uw_buoyancy)
1941  else if (name .eq. "vw_buoyancy_local" .and. allocated(vw_buoyancy)) then
1942  call set_published_field_value(field_value, real_1d_field=vw_buoyancy)
1943  else if (name .eq. "uw_tendency_local" .and. allocated(uw_tendency)) then
1944  call set_published_field_value(field_value, real_1d_field=uw_tendency)
1945  else if (name .eq. "vw_tendency_local" .and. allocated(vw_tendency)) then
1946  call set_published_field_value(field_value, real_1d_field=vw_tendency)
1947  else if (name .eq. "uw_w_local" .and. allocated(uw_w)) then
1948  call set_published_field_value(field_value, real_1d_field=uw_w)
1949  else if (name .eq. "vw_w_local" .and. allocated(vw_w)) then
1950  call set_published_field_value(field_value, real_1d_field=vw_w)
1951  else if (name .eq. "tu_su_local" .and. allocated(tu_su)) then
1952  call set_published_field_value(field_value, real_1d_field=tu_su)
1953  else if (name .eq. "uu_advection_local" .and. allocated(uu_advection)) then
1954  call set_published_field_value(field_value, real_1d_field=uu_advection)
1955  else if (name .eq. "uu_viscosity_local" .and. allocated(uu_viscosity)) then
1956  call set_published_field_value(field_value, real_1d_field=uu_viscosity)
1957  else if (name .eq. "wu_u_local" .and. allocated(wu_u)) then
1958  call set_published_field_value(field_value, real_1d_field=wu_u)
1959  else if (name .eq. "tv_sv_local" .and. allocated(tv_sv)) then
1960  call set_published_field_value(field_value, real_1d_field=tv_sv)
1961  else if (name .eq. "vv_advection_local" .and. allocated(vv_advection)) then
1962  call set_published_field_value(field_value, real_1d_field=vv_advection)
1963  else if (name .eq. "vv_viscosity_local" .and. allocated(vv_viscosity)) then
1964  call set_published_field_value(field_value, real_1d_field=vv_viscosity)
1965  else if (name .eq. "wv_v_local" .and. allocated(wv_v)) then
1966  call set_published_field_value(field_value, real_1d_field=wv_v)
1967  else if (name .eq. "tw_sw_local" .and. allocated(tw_sw)) then
1968  call set_published_field_value(field_value, real_1d_field=tw_sw)
1969  else if (name .eq. "ww_advection_local" .and. allocated(ww_advection)) then
1970  call set_published_field_value(field_value, real_1d_field=ww_advection)
1971  else if (name .eq. "ww_viscosity_local" .and. allocated(ww_viscosity)) then
1972  call set_published_field_value(field_value, real_1d_field=ww_viscosity)
1973  else if (name .eq. "ww_buoyancy_local" .and. allocated(ww_buoyancy)) then
1974  call set_published_field_value(field_value, real_1d_field=ww_buoyancy)
1975  else if (name .eq. "u_thetal_local" .and. allocated(u_thetal)) then
1976  call set_published_field_value(field_value, real_1d_field=u_thetal)
1977  else if (name .eq. "us_thetal_local" .and. allocated(us_thetal)) then
1978  call set_published_field_value(field_value, real_1d_field=us_thetal)
1979  else if (name .eq. "u_thetal_advection_local" .and. allocated(u_thetal_advection)) then
1980  call set_published_field_value(field_value, real_1d_field=u_thetal_advection)
1981  else if (name .eq. "u_thetal_viscosity_diffusion_local" .and. allocated(u_thetal_viscosity_diffusion)) then
1982  call set_published_field_value(field_value, real_1d_field=u_thetal_viscosity_diffusion)
1983  else if (name .eq. "wu_thetal_local" .and. allocated(wu_thetal)) then
1984  call set_published_field_value(field_value, real_1d_field=wu_thetal)
1985  else if (name .eq. "v_thetal_local" .and. allocated(v_thetal)) then
1986  call set_published_field_value(field_value, real_1d_field=v_thetal)
1987  else if (name .eq. "vs_thetal_local" .and. allocated(vs_thetal)) then
1988  call set_published_field_value(field_value, real_1d_field=vs_thetal)
1989  else if (name .eq. "v_thetal_advection_local" .and. allocated(v_thetal_advection)) then
1990  call set_published_field_value(field_value, real_1d_field=v_thetal_advection)
1991  else if (name .eq. "v_thetal_viscosity_diffusion_local" .and. allocated(v_thetal_viscosity_diffusion)) then
1992  call set_published_field_value(field_value, real_1d_field=v_thetal_viscosity_diffusion)
1993  else if (name .eq. "wv_thetal_local" .and. allocated(wv_thetal)) then
1994  call set_published_field_value(field_value, real_1d_field=wv_thetal)
1995  else if (name .eq. "w_thetal_local" .and. allocated(w_thetal)) then
1996  call set_published_field_value(field_value, real_1d_field=w_thetal)
1997  else if (name .eq. "ws_thetal_local" .and. allocated(ws_thetal)) then
1998  call set_published_field_value(field_value, real_1d_field=ws_thetal)
1999  else if (name .eq. "w_thetal_advection_local" .and. allocated(w_thetal_advection)) then
2000  call set_published_field_value(field_value, real_1d_field=w_thetal_advection)
2001  else if (name .eq. "w_thetal_viscosity_diffusion_local" .and. allocated(w_thetal_viscosity_diffusion)) then
2002  call set_published_field_value(field_value, real_1d_field=w_thetal_viscosity_diffusion)
2003  else if (name .eq. "w_thetal_buoyancy_local" .and. allocated(w_thetal_buoyancy)) then
2004  call set_published_field_value(field_value, real_1d_field=w_thetal_buoyancy)
2005  else if (name .eq. "ww_thetal_local" .and. allocated(ww_thetal)) then
2006  call set_published_field_value(field_value, real_1d_field=ww_thetal)
2007  else if (name .eq. "thetal_thetal_local" .and. allocated(thetal_thetal)) then
2008  call set_published_field_value(field_value, real_1d_field=thetal_thetal)
2009  else if (name .eq. "sthetal_thetal_local" .and. allocated(sthetal_thetal)) then
2010  call set_published_field_value(field_value, real_1d_field=sthetal_thetal)
2011  else if (name .eq. "thetal_thetal_advection_local" .and. allocated(thetal_thetal_advection)) then
2012  call set_published_field_value(field_value, real_1d_field=thetal_thetal_advection)
2013  else if (name .eq. "thetal_thetal_diffusion_local" .and. allocated(thetal_thetal_diffusion)) then
2014  call set_published_field_value(field_value, real_1d_field=thetal_thetal_diffusion)
2015  else if (name .eq. "wthetal_thetal_local" .and. allocated(wthetal_thetal)) then
2016  call set_published_field_value(field_value, real_1d_field=wthetal_thetal)
2017  else if (name .eq. "u_mse_local" .and. allocated(u_mse)) then
2018  call set_published_field_value(field_value, real_1d_field=u_mse)
2019  else if (name .eq. "us_mse_local" .and. allocated(us_mse)) then
2020  call set_published_field_value(field_value, real_1d_field=us_mse)
2021  else if (name .eq. "u_mse_advection_local" .and. allocated(u_mse_advection)) then
2022  call set_published_field_value(field_value, real_1d_field=u_mse_advection)
2023  else if (name .eq. "u_mse_viscosity_diffusion_local" .and. allocated(u_mse_viscosity_diffusion)) then
2024  call set_published_field_value(field_value, real_1d_field=u_mse_viscosity_diffusion)
2025  else if (name .eq. "wu_mse_local" .and. allocated(wu_mse)) then
2026  call set_published_field_value(field_value, real_1d_field=wu_mse)
2027  else if (name .eq. "v_mse_local" .and. allocated(v_mse)) then
2028  call set_published_field_value(field_value, real_1d_field=v_mse)
2029  else if (name .eq. "vs_mse_local" .and. allocated(vs_mse)) then
2030  call set_published_field_value(field_value, real_1d_field=vs_mse)
2031  else if (name .eq. "v_mse_advection_local" .and. allocated(v_mse_advection)) then
2032  call set_published_field_value(field_value, real_1d_field=v_mse_advection)
2033  else if (name .eq. "v_mse_viscosity_diffusion_local" .and. allocated(v_mse_viscosity_diffusion)) then
2034  call set_published_field_value(field_value, real_1d_field=v_mse_viscosity_diffusion)
2035  else if (name .eq. "wv_mse_local" .and. allocated(wv_mse)) then
2036  call set_published_field_value(field_value, real_1d_field=wv_mse)
2037  else if (name .eq. "w_mse_local" .and. allocated(w_mse)) then
2038  call set_published_field_value(field_value, real_1d_field=w_mse)
2039  else if (name .eq. "ws_mse_local" .and. allocated(ws_mse)) then
2040  call set_published_field_value(field_value, real_1d_field=ws_mse)
2041  else if (name .eq. "w_mse_advection_local" .and. allocated(w_mse_advection)) then
2042  call set_published_field_value(field_value, real_1d_field=w_mse_advection)
2043  else if (name .eq. "w_mse_viscosity_diffusion_local" .and. allocated(w_mse_viscosity_diffusion)) then
2044  call set_published_field_value(field_value, real_1d_field=w_mse_viscosity_diffusion)
2045  else if (name .eq. "w_mse_buoyancy_local" .and. allocated(w_mse_buoyancy)) then
2046  call set_published_field_value(field_value, real_1d_field=w_mse_buoyancy)
2047  else if (name .eq. "ww_mse_local" .and. allocated(ww_mse)) then
2048  call set_published_field_value(field_value, real_1d_field=ww_mse)
2049  else if (name .eq. "mse_mse_local" .and. allocated(mse_mse)) then
2050  call set_published_field_value(field_value, real_1d_field=mse_mse)
2051  else if (name .eq. "smse_mse_local" .and. allocated(smse_mse)) then
2052  call set_published_field_value(field_value, real_1d_field=smse_mse)
2053  else if (name .eq. "mse_mse_advection_local" .and. allocated(mse_mse_advection)) then
2054  call set_published_field_value(field_value, real_1d_field=mse_mse_advection)
2055  else if (name .eq. "mse_mse_diffusion_local" .and. allocated(mse_mse_diffusion)) then
2056  call set_published_field_value(field_value, real_1d_field=mse_mse_diffusion)
2057  else if (name .eq. "wmse_mse_local" .and. allocated(wmse_mse)) then
2058  call set_published_field_value(field_value, real_1d_field=wmse_mse)
2059  else if (name .eq. "us_qt_local" .and. allocated(us_qt)) then
2060  call set_published_field_value(field_value, real_1d_field=us_qt)
2061  else if (name .eq. "u_qt_advection_local" .and. allocated(u_qt_advection)) then
2062  call set_published_field_value(field_value, real_1d_field=u_qt_advection)
2063  else if (name .eq. "u_qt_viscosity_diffusion_local" .and. allocated(u_qt_viscosity_diffusion)) then
2064  call set_published_field_value(field_value, real_1d_field=u_qt_viscosity_diffusion)
2065  else if (name .eq. "wu_qt_local" .and. allocated(wu_qt)) then
2066  call set_published_field_value(field_value, real_1d_field=wu_qt)
2067  else if (name .eq. "vs_qt_local" .and. allocated(vs_qt)) then
2068  call set_published_field_value(field_value, real_1d_field=vs_qt)
2069  else if (name .eq. "v_qt_advection_local" .and. allocated(v_qt_advection)) then
2070  call set_published_field_value(field_value, real_1d_field=v_qt_advection)
2071  else if (name .eq. "v_qt_viscosity_diffusion_local" .and. allocated(v_qt_viscosity_diffusion)) then
2072  call set_published_field_value(field_value, real_1d_field=v_qt_viscosity_diffusion)
2073  else if (name .eq. "wv_qt_local" .and. allocated(wv_qt)) then
2074  call set_published_field_value(field_value, real_1d_field=wv_qt)
2075  else if (name .eq. "w_qt_local" .and. allocated(w_qt)) then
2076  call set_published_field_value(field_value, real_1d_field=w_qt)
2077  else if (name .eq. "ws_qt_local" .and. allocated(ws_qt)) then
2078  call set_published_field_value(field_value, real_1d_field=ws_qt)
2079  else if (name .eq. "w_qt_advection_local" .and. allocated(w_qt_advection)) then
2080  call set_published_field_value(field_value, real_1d_field=w_qt_advection)
2081  else if (name .eq. "w_qt_viscosity_diffusion_local" .and. allocated(w_qt_viscosity_diffusion)) then
2082  call set_published_field_value(field_value, real_1d_field=w_qt_viscosity_diffusion)
2083  else if (name .eq. "w_qt_buoyancy_local" .and. allocated(w_qt_buoyancy)) then
2084  call set_published_field_value(field_value, real_1d_field=w_qt_buoyancy)
2085  else if (name .eq. "ww_qt_local" .and. allocated(ww_qt)) then
2086  call set_published_field_value(field_value, real_1d_field=ww_qt)
2087  else if (name .eq. "qt_qt_local" .and. allocated(qt_qt)) then
2088  call set_published_field_value(field_value, real_1d_field=qt_qt)
2089  else if (name .eq. "sqt_qt_local" .and. allocated(sqt_qt)) then
2090  call set_published_field_value(field_value, real_1d_field=sqt_qt)
2091  else if (name .eq. "qt_qt_advection_local" .and. allocated(qt_qt_advection)) then
2092  call set_published_field_value(field_value, real_1d_field=qt_qt_advection)
2093  else if (name .eq. "qt_qt_diffusion_local" .and. allocated(qt_qt_diffusion)) then
2094  call set_published_field_value(field_value, real_1d_field=qt_qt_diffusion)
2095  else if (name .eq. "wqt_qt_local" .and. allocated(wqt_qt)) then
2096  call set_published_field_value(field_value, real_1d_field=wqt_qt)
2097  else if (name .eq. "mflux_local") then
2098  field_value%scalar_real=mflux
2099  end if
2100  end subroutine field_value_retrieval_callback
2101 
2106  subroutine set_published_field_value(field_value, real_1d_field, real_2d_field)
2107  type(component_field_value_type), intent(inout) :: field_value
2108  real(kind=DEFAULT_PRECISION), dimension(:), optional :: real_1d_field
2109  real(kind=DEFAULT_PRECISION), dimension(:,:), optional :: real_2d_field
2110 
2111  if (present(real_1d_field)) then
2112  allocate(field_value%real_1d_array(size(real_1d_field)), source=real_1d_field)
2113  else if (present(real_2d_field)) then
2114  allocate(field_value%real_2d_array(size(real_2d_field, 1), size(real_2d_field, 2)), source=real_2d_field)
2115  end if
2116  end subroutine set_published_field_value
2117 
2122  subroutine set_published_field_enabled_state(collection, field_name, enabled_state)
2123  type(hashmap_type), intent(inout) :: collection
2124  character(len=*), intent(in) :: field_name
2125  logical, intent(in) :: enabled_state
2126 
2127  call c_put_logical(collection, field_name, enabled_state)
2128  end subroutine set_published_field_enabled_state
2129 
2134  logical function get_published_field_enabled_state(collection, field_name)
2135  type(hashmap_type), intent(inout) :: collection
2136  character(len=*), intent(in) :: field_name
2137 
2138  get_published_field_enabled_state=c_get_logical(collection, field_name)
2140 end module flux_budget_mod
real(kind=default_precision), dimension(:), allocatable ww_qt
Definition: flux_budget.F90:19
Gets a specific logical element out of the list, stack, queue or map with the corresponding key...
subroutine initialise_thetal_diagnostics(current_state)
Initialises the thetal diagnostics.
logical some_uw_vw_diagnostics_enabled
Definition: flux_budget.F90:36
logical some_mse_diagnostics_enabled
Definition: flux_budget.F90:36
type(hashmap_type) q_flux_fields
Definition: flux_budget.F90:33
real(kind=default_precision), dimension(:), allocatable v_mse_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable wv_qt
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable u_thetal
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable mse_mse_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable tu_su
Definition: flux_budget.F90:19
type(hashmap_type) prognostic_budget_fields
Definition: flux_budget.F90:33
Wrapper type for the value returned for a published field from a component.
real(kind=default_precision), dimension(:), allocatable th_gradient
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable ww_buoyancy
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable u_mse_viscosity_diffusion
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable u_qt_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable mse_mse
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable th_flux_values
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable u_thetal_viscosity_diffusion
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable uw_advection
Definition: flux_budget.F90:19
subroutine clear_thetal()
Clears the thetal diagnostics.
real(kind=default_precision), dimension(:), allocatable u_qt_viscosity_diffusion
Definition: flux_budget.F90:19
real(kind=default_precision) wmfcrit
Definition: flux_budget.F90:31
real(kind=default_precision), dimension(:), allocatable vw_viscosity
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable th_diff
Definition: flux_budget.F90:19
subroutine compute_q_flux_for_column(current_state)
Computes the Q flux diagnostics for a specific column.
logical function is_field_qt(name)
Determines whether a specific published field is a mse field.
real(kind=default_precision), dimension(:), allocatable u_mse
Definition: flux_budget.F90:19
subroutine clear_uw_vw()
Clears the uw uv diagnostics.
real(kind=default_precision), dimension(:), allocatable w_qt_advection
Definition: flux_budget.F90:19
subroutine set_published_field_value(field_value, real_1d_field, real_2d_field)
Sets the published field value from the temporary diagnostic values held by this component.
type(hashmap_type) mse_fields
Definition: flux_budget.F90:33
real(kind=default_precision), dimension(:), allocatable ww_mse
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable us_mse
Definition: flux_budget.F90:19
logical some_thetal_diagnostics_enabled
Definition: flux_budget.F90:36
real(kind=default_precision), dimension(:), allocatable ws_thetal
Definition: flux_budget.F90:19
subroutine field_information_retrieval_callback(current_state, name, field_information)
Field information retrieval callback, this returns information for a specific components published fi...
subroutine clear_qt()
Clears the qt diagnostics.
type(hashmap_type) qt_fields
Definition: flux_budget.F90:33
real(kind=default_precision), dimension(:), allocatable uu_viscosity
Definition: flux_budget.F90:19
logical function, public is_component_field_available(name)
Determines whether a specific published field is available or not.
Definition: registry.F90:135
subroutine initialise_mse_diagnostics(current_state)
Initialises the mse diagnostics. For now we are assuming mse is the same as theta, which needs updating with moisture information.
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17
integer, parameter, public z_index
Grid index parameters.
Definition: grids.F90:14
subroutine initialisation_callback(current_state)
Initialisation call back.
real(kind=default_precision), dimension(:), allocatable v_thetal_viscosity_diffusion
Definition: flux_budget.F90:19
subroutine set_published_field_enabled_state(collection, field_name, enabled_state)
Sets the published value enabled state in the provided collection map.
real(kind=default_precision), dimension(:), allocatable w_thetal_viscosity_diffusion
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable vs_thetal
Definition: flux_budget.F90:19
Contains common definitions for the data and datatypes used by MONC.
Definition: datadefn.F90:2
subroutine compute_scalars_for_column(current_state)
Computes the scalar diagnostics for a specific column.
real(kind=default_precision), dimension(:), allocatable v_mse_viscosity_diffusion
Definition: flux_budget.F90:19
The ModelState which represents the current state of a run.
Definition: state.F90:39
real(kind=default_precision), dimension(:), allocatable w_mse
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable vv_viscosity
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable wu_thetal
Definition: flux_budget.F90:19
A hashmap structure, the same as a map but uses hashing for greatly improved performance when storing...
Definition: collections.F90:94
real(kind=default_precision), dimension(:), allocatable thetal_thetal_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable w_qt
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable uw_w
Definition: flux_budget.F90:19
subroutine initialise_scalar_diagnostics(current_state)
Initialises the scalar diagnostics.
real(kind=default_precision), dimension(:), allocatable wu_qt
Definition: flux_budget.F90:19
subroutine initialise_qt_diagnostics(current_state)
Initialises the qt diagnostics. For now we are assuming qt is the same as theta, which needs updating...
logical function is_field_scalar(name)
Determines whether a specific published field is a scalar field.
real(kind=default_precision), dimension(:), allocatable smse_mse
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable v_thetal_advection
Definition: flux_budget.F90:19
logical some_theta_flux_diagnostics_enabled
Definition: flux_budget.F90:36
subroutine clear_prognostic_budgets()
Clears the prognostic (uu, vv, ww) budgets.
real(kind=default_precision), dimension(:), allocatable vv_advection
Definition: flux_budget.F90:19
subroutine initialise_uw_vw_diagnostics(current_state)
Initialises the UW and VW diagnostics.
real(kind=default_precision), dimension(:), allocatable ws_mse
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable us_thetal
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable w_thetal
Definition: flux_budget.F90:19
integer, parameter, public component_array_field_type
real(kind=default_precision), dimension(:), allocatable vw_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable qt_qt_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable w_mse_buoyancy
Definition: flux_budget.F90:19
Puts a logical key-value pair into the map.
subroutine clear_theta_fluxes()
Clears the heat flux diagnostics at the start of a timestep.
type(component_field_value_type) function, public get_component_field_value(current_state, name)
Retrieves the value wrapper of a components published field.
Definition: registry.F90:144
real(kind=default_precision), dimension(:), allocatable w_thetal_buoyancy
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable w_mse_viscosity_diffusion
Definition: flux_budget.F90:19
subroutine initialise_q_flux_diagnostics(current_state)
Initialises the Q field flux diagnostic areas and enabled flags depending upon the configuration of t...
subroutine clear_scalars()
Clears the scalar diagnostics.
real(kind=default_precision), dimension(:,:), allocatable q_tendency
Definition: flux_budget.F90:32
subroutine initialise_theta_flux_diagnostics(current_state)
Initialises the heat flux diagnostic areas and enabled flags depending upon the configuration of the ...
subroutine compute_thetal_for_column(current_state)
Computes the thetal diagnostics for a specific column.
Defines the global grid.
Definition: grids.F90:100
real(kind=default_precision), dimension(:), allocatable us_qt
Definition: flux_budget.F90:19
type(component_descriptor_type) function, public flux_budget_get_descriptor()
Provides the descriptor back to the caller and is used in component registration. ...
Definition: flux_budget.F90:47
type(hashmap_type) thetal_fields
Definition: flux_budget.F90:33
Returns the number of elements in the collection.
real(kind=default_precision), dimension(:), allocatable v_qt_viscosity_diffusion
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable w_qt_viscosity_diffusion
Definition: flux_budget.F90:19
type(component_field_information_type) function, public get_component_field_information(current_state, name)
Retrieves information about a components published field which includes its type and size...
Definition: registry.F90:165
Interfaces and types that MONC components must specify.
logical function is_field_mse(name)
Determines whether a specific published field is a mse field.
real(kind=default_precision), dimension(:), allocatable wu_mse
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable th_buoyancy
Definition: flux_budget.F90:19
Defined the local grid, i.e. the grid held on this process after decomposition.
Definition: grids.F90:111
real(kind=default_precision), dimension(:), allocatable ws_qt
Definition: flux_budget.F90:19
subroutine populate_field_names()
Populates the published field names in the appropriate map.
Collection data structures.
Definition: collections.F90:7
real(kind=default_precision), dimension(:), allocatable sqt_qt
Definition: flux_budget.F90:19
subroutine finalisation_callback(current_state)
Finalisation call back.
subroutine compute_uw_vw_for_column(current_state)
Computes the uw uv diagnostics for a specific column.
real(kind=default_precision), dimension(:,:), allocatable q_flux_values
Definition: flux_budget.F90:32
real(kind=default_precision), dimension(:), allocatable w_thetal_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:,:), allocatable q_buoyancy
Definition: flux_budget.F90:32
real(kind=default_precision) mflux
Definition: flux_budget.F90:31
subroutine timestep_callback(current_state)
Timestep call back, this will deduce the diagnostics for the current (non halo) column.
real(kind=default_precision), dimension(:), allocatable thetal_thetal
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable wthetal_thetal
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:,:), allocatable q_diff
Definition: flux_budget.F90:32
real(kind=default_precision), dimension(:), allocatable u_mse_advection
Definition: flux_budget.F90:19
logical some_prognostic_budget_diagnostics_enabled
Definition: flux_budget.F90:36
real(kind=default_precision), dimension(:), allocatable w_mse_advection
Definition: flux_budget.F90:19
logical function is_field_prognostic_budget(name)
Determines whether a specific published field is a uu, vv or ww field.
real(kind=default_precision), dimension(:), allocatable wu_u
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable ww_advection
Definition: flux_budget.F90:19
real(kind=default_precision) function, public options_get_real(options_database, key, index)
Retrieves a real value from the database that matches the provided key.
real(kind=default_precision), dimension(:), allocatable v_mse
Definition: flux_budget.F90:19
Functionality to support the different types of grid and abstraction between global grids and local o...
Definition: grids.F90:5
real(kind=default_precision), dimension(:), allocatable uw_viscosity
Definition: flux_budget.F90:19
logical function is_field_q_flux(name)
Determines whether a specific published field is a q flux field.
integer function, public options_get_integer(options_database, key, index)
Retrieves an integer value from the database that matches the provided key.
subroutine compute_mse_for_column(current_state)
Computes the mse diagnostics for a specific column. For now we are assuming mse is the same as theta...
logical function is_field_uw_vw(name)
Determines whether a specific published field is a uw or uv field.
Manages the options database. Contains administration functions and deduce runtime options from the c...
real(kind=default_precision), dimension(:), allocatable ww_thetal
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable qt_qt
Definition: flux_budget.F90:19
subroutine initialise_prognostic_budget_diagnostics(current_state)
Initialises the prognostic (uu, vv, ww) budget diagnostics.
real(kind=default_precision), dimension(:), allocatable v_thetal
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable mse_mse_diffusion
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:,:), allocatable q_gradient
Definition: flux_budget.F90:32
subroutine clear_q_fluxes()
Clears the Q flux diagnostics, called at the start of a timestep.
type(hashmap_type) scalar_fields
Definition: flux_budget.F90:33
real(kind=default_precision), dimension(:), allocatable wqt_qt
Definition: flux_budget.F90:19
subroutine field_value_retrieval_callback(current_state, name, field_value)
Field value retrieval callback, this returns the value of a specific published field.
subroutine compute_theta_flux_for_column(current_state)
Computes the heat flux diagnostics for a specific column.
real(kind=default_precision), dimension(:), allocatable v_qt_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable uw_tendency
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable th_tendency
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable w_qt_buoyancy
Definition: flux_budget.F90:19
Flux budget component which produces diagnostic data for the flux aspects of the model.
Definition: flux_budget.F90:2
Determines whether or not a map contains a specific key.
logical some_q_flux_diagnostics_enabled
Definition: flux_budget.F90:36
real(kind=default_precision), dimension(:), allocatable vs_qt
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable uw_buoyancy
Definition: flux_budget.F90:19
subroutine clear_mse()
Clears the mse diagnostics.
real(kind=default_precision), dimension(:), allocatable thetal_thetal_diffusion
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable wv_thetal
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable qt_qt_diffusion
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable u_thetal_advection
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable wmse_mse
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable vw_tendency
Definition: flux_budget.F90:19
subroutine compute_prognostic_budgets_for_column(current_state)
Computes the prognostic (uu, vv, ww) budgets for a specific column.
The model state which represents the current state of a run.
Definition: state.F90:2
real(kind=default_precision), dimension(:), allocatable uu_advection
Definition: flux_budget.F90:19
integer, parameter, public y_index
Definition: grids.F90:14
real(kind=default_precision), dimension(:), allocatable vw_w
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable wv_v
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable tv_sv
Definition: flux_budget.F90:19
type(hashmap_type) uw_vw_fields
Definition: flux_budget.F90:33
integer diagnostic_generation_frequency
Definition: flux_budget.F90:39
real(kind=default_precision), dimension(:), allocatable sthetal_thetal
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable ww_viscosity
Definition: flux_budget.F90:19
type(hashmap_type) heat_flux_fields
Definition: flux_budget.F90:33
real(kind=default_precision), dimension(:), allocatable tw_sw
Definition: flux_budget.F90:19
logical function is_field_heat_flux(name)
Determines whether a specific published field is a heat flux field.
real(kind=default_precision), dimension(:), allocatable vw_buoyancy
Definition: flux_budget.F90:19
integer, parameter, public x_index
Definition: grids.F90:14
subroutine compute_qt_for_column(current_state)
Computes the qt diagnostics for a specific column. For now we are assuming qt is the same as theta...
real(kind=default_precision), dimension(:), allocatable wv_mse
Definition: flux_budget.F90:19
real(kind=default_precision), dimension(:), allocatable vs_mse
Definition: flux_budget.F90:19
logical some_qt_diagnostics_enabled
Definition: flux_budget.F90:36
logical function is_field_thetal(name)
Determines whether a specific published field is a thetal field.
logical function get_published_field_enabled_state(collection, field_name)
Retrieves whether a published field is enabled or not.
MONC component registry.
Definition: registry.F90:5
integer, parameter, public component_double_data_type