MONC
Functions/Subroutines | Variables
subgrid_profile_diagnostics_mod Module Reference

Functions/Subroutines

type(component_descriptor_type) function, public subgrid_profile_diagnostics_get_descriptor ()
 Provides the component descriptor for the core to register. More...
 
subroutine initialisation_callback (current_state)
 
subroutine timestep_callback (current_state)
 
subroutine field_information_retrieval_callback (current_state, name, field_information)
 Field information retrieval callback, this returns information for a specific components published field. More...
 
subroutine field_value_retrieval_callback (current_state, name, field_value)
 Field value retrieval callback, this returns the value of a specific published field. More...
 

Variables

integer total_points
 
integer iqv
 
integer iql
 
real(kind=default_precision), dimension(:), allocatable uwsg_tot
 
real(kind=default_precision), dimension(:), allocatable vwsg_tot
 
real(kind=default_precision), dimension(:), allocatable uusg_tot
 
real(kind=default_precision), dimension(:), allocatable vvsg_tot
 
real(kind=default_precision), dimension(:), allocatable wwsg_tot
 
real(kind=default_precision), dimension(:), allocatable tkesg_tot
 
real(kind=default_precision), dimension(:), allocatable wtsg_tot
 
real(kind=default_precision), dimension(:), allocatable th2sg_tot
 
real(kind=default_precision), dimension(:), allocatable wqsg_tot
 
real(kind=default_precision), dimension(:), allocatable dissipation
 
real(kind=default_precision), dimension(:), allocatable epsth
 
real(kind=default_precision), dimension(:), allocatable ssq
 
real(kind=default_precision), dimension(:), allocatable elamr_sq
 
real(kind=default_precision), dimension(:), allocatable richardson_number
 
real(kind=default_precision), dimension(:), allocatable subgrid_tke
 
real(kind=default_precision) a2_n
 
real(kind=default_precision) ath2_n
 
real(kind=default_precision) pr_n
 
real(kind=default_precision) ri_crit
 
real(kind=default_precision) qlcrit
 

Function/Subroutine Documentation

◆ field_information_retrieval_callback()

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

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

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

Definition at line 253 of file subgrid_profile_diagnostics.F90.

253  type(model_state_type), target, intent(inout) :: current_state
254  character(len=*), intent(in) :: name
255  type(component_field_information_type), intent(out) :: field_information
256 
257  field_information%field_type=component_array_field_type
258  field_information%number_dimensions=1
259  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
260  field_information%data_type=component_double_data_type
261 
262  if (name .eq. "th2sg_total_local") then
263  field_information%enabled=current_state%th%active
264  else if (name .eq. "wqsg_total_local") then
265  field_information%enabled= (.not.current_state%passive_q) .and. &
266  (current_state%liquid_water_mixing_ratio_index > 0)
267 ! ========================================================================
268 ! 2nd stream
269  else if (name .eq. "i_th2sg_total_local") then
270  field_information%enabled=current_state%th%active
271  else if (name .eq. "i_wqsg_total_local") then
272  field_information%enabled= (.not.current_state%passive_q) .and. &
273  (current_state%liquid_water_mixing_ratio_index > 0)
274 ! ========================================================================
275  else
276  field_information%enabled=.true.
277  end if
Here is the caller graph for this function:

◆ field_value_retrieval_callback()

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

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

Parameters
current_stateCurrent model state
nameThe name of the field to retrieve the value for
field_valuePopulated with the value of the field

Definition at line 285 of file subgrid_profile_diagnostics.F90.

285  type(model_state_type), target, intent(inout) :: current_state
286  character(len=*), intent(in) :: name
287  type(component_field_value_type), intent(out) :: field_value
288 
289  integer :: k
290 
291  if (name .eq. "uwsg_total_local") then
292  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
293  do k = 1, current_state%local_grid%size(z_index)
294  field_value%real_1d_array(k)=uwsg_tot(k)
295  enddo
296  else if (name .eq. "vwsg_total_local") then
297  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
298  do k = 1, current_state%local_grid%size(z_index)
299  field_value%real_1d_array(k)=vwsg_tot(k)
300  enddo
301  else if (name .eq. "uusg_total_local") then
302  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
303  do k = 1, current_state%local_grid%size(z_index)
304  field_value%real_1d_array(k)=uusg_tot(k)
305  enddo
306  else if (name .eq. "vvsg_total_local") then
307  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
308  do k = 1, current_state%local_grid%size(z_index)
309  field_value%real_1d_array(k)=vvsg_tot(k)
310  enddo
311  else if (name .eq. "wwsg_total_local") then
312  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
313  do k = 1, current_state%local_grid%size(z_index)
314  field_value%real_1d_array(k)=wwsg_tot(k)
315  enddo
316  else if (name .eq. "tkesg_total_local") then
317  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
318  do k = 1, current_state%local_grid%size(z_index)
319  field_value%real_1d_array(k)=tkesg_tot(k)
320  enddo
321  else if (name .eq. "wtsg_total_local") then
322  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
323  do k = 1, current_state%local_grid%size(z_index)
324  field_value%real_1d_array(k)=wtsg_tot(k)
325  enddo
326  else if (name .eq. "th2sg_total_local") then
327  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
328  do k = 1, current_state%local_grid%size(z_index)
329  field_value%real_1d_array(k)=th2sg_tot(k)
330  enddo
331  else if (name .eq. "wqsg_total_local") then
332  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
333  do k = 1, current_state%local_grid%size(z_index)
334  field_value%real_1d_array(k)=wqsg_tot(k)
335  enddo
336 ! =====================================================
337 ! 2nd stream
338  else if (name .eq. "i_uwsg_total_local") then
339  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
340  do k = 1, current_state%local_grid%size(z_index)
341  field_value%real_1d_array(k)=uwsg_tot(k)
342  enddo
343  else if (name .eq. "i_vwsg_total_local") then
344  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
345  do k = 1, current_state%local_grid%size(z_index)
346  field_value%real_1d_array(k)=vwsg_tot(k)
347  enddo
348  else if (name .eq. "i_uusg_total_local") then
349  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
350  do k = 1, current_state%local_grid%size(z_index)
351  field_value%real_1d_array(k)=uusg_tot(k)
352  enddo
353  else if (name .eq. "i_vvsg_total_local") then
354  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
355  do k = 1, current_state%local_grid%size(z_index)
356  field_value%real_1d_array(k)=vvsg_tot(k)
357  enddo
358  else if (name .eq. "i_wwsg_total_local") then
359  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
360  do k = 1, current_state%local_grid%size(z_index)
361  field_value%real_1d_array(k)=wwsg_tot(k)
362  enddo
363  else if (name .eq. "i_tkesg_total_local") then
364  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
365  do k = 1, current_state%local_grid%size(z_index)
366  field_value%real_1d_array(k)=tkesg_tot(k)
367  enddo
368  else if (name .eq. "i_wtsg_total_local") then
369  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
370  do k = 1, current_state%local_grid%size(z_index)
371  field_value%real_1d_array(k)=wtsg_tot(k)
372  enddo
373  else if (name .eq. "i_th2sg_total_local") then
374  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
375  do k = 1, current_state%local_grid%size(z_index)
376  field_value%real_1d_array(k)=th2sg_tot(k)
377  enddo
378  else if (name .eq. "i_wqsg_total_local") then
379  allocate(field_value%real_1d_array(current_state%local_grid%size(z_index)))
380  do k = 1, current_state%local_grid%size(z_index)
381  field_value%real_1d_array(k)=wqsg_tot(k)
382  enddo
383 ! =====================================================
384  end if
Here is the caller graph for this function:

◆ initialisation_callback()

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

Definition at line 82 of file subgrid_profile_diagnostics.F90.

82  type(model_state_type), target, intent(inout) :: current_state
83 
84  integer :: k
85 
86  if (.not. is_component_enabled(current_state%options_database, "smagorinsky")) then
87  call log_master_log(log_error, "Subgrid model diags requested but subgrid model not enabled - check config")
88  end if
89 
90  total_points=(current_state%local_grid%size(y_index) * current_state%local_grid%size(x_index))
91 
92  allocate(uwsg_tot(current_state%local_grid%size(z_index)) &
93  , vwsg_tot(current_state%local_grid%size(z_index)) &
94  , uusg_tot(current_state%local_grid%size(z_index)) &
95  , vvsg_tot(current_state%local_grid%size(z_index)) &
96  , wwsg_tot(current_state%local_grid%size(z_index)) &
97  , tkesg_tot(current_state%local_grid%size(z_index)) &
98  , wtsg_tot(current_state%local_grid%size(z_index)) &
99  , th2sg_tot(current_state%local_grid%size(z_index)) &
100  , wqsg_tot(current_state%local_grid%size(z_index)) )
101 ! Allocation of dissipation should in due course be made conditional.
102 ! Check sonsistency of any changes with the deallocations later.
103  allocate(dissipation(current_state%local_grid%size(z_index)))
104  allocate(epsth(current_state%local_grid%size(z_index)))
105  allocate(ssq(current_state%local_grid%size(z_index)))
106  allocate(elamr_sq(current_state%local_grid%size(z_index)))
107  allocate(richardson_number(current_state%local_grid%size(z_index)))
108  allocate(subgrid_tke(current_state%local_grid%size(z_index)))
109 
110 
111  if (.not. current_state%passive_q .and. current_state%number_q_fields .gt. 0) then
112  iqv=get_q_index(standard_q_names%VAPOUR, 'subgrid_profile_diags')
113  iql=get_q_index(standard_q_names%CLOUD_LIQUID_MASS, 'subgrid_profile_diags')
114  qlcrit=options_get_real(current_state%options_database, "qlcrit")
115  endif
116 
Here is the caller graph for this function:

◆ subgrid_profile_diagnostics_get_descriptor()

type(component_descriptor_type) function, public subgrid_profile_diagnostics_mod::subgrid_profile_diagnostics_get_descriptor ( )

Provides the component descriptor for the core to register.

Returns
The descriptor describing this component

Definition at line 43 of file subgrid_profile_diagnostics.F90.

43  subgrid_profile_diagnostics_get_descriptor%name="subgrid_profile_diagnostics"
44  subgrid_profile_diagnostics_get_descriptor%version=0.1
45 
46  subgrid_profile_diagnostics_get_descriptor%initialisation=>initialisation_callback
47  subgrid_profile_diagnostics_get_descriptor%timestep=>timestep_callback
48 
49  subgrid_profile_diagnostics_get_descriptor%field_value_retrieval=>field_value_retrieval_callback
50  subgrid_profile_diagnostics_get_descriptor%field_information_retrieval=>field_information_retrieval_callback
51 ! Note: Multiple copies of diagnostics are required for different time processing, so
52 ! duplicate the variables as often as necessary
53  allocate(subgrid_profile_diagnostics_get_descriptor%published_fields(2*(5+2+9)))
54 
55  subgrid_profile_diagnostics_get_descriptor%published_fields(1)="uwsg_total_local"
56  subgrid_profile_diagnostics_get_descriptor%published_fields(2)="vwsg_total_local"
57  subgrid_profile_diagnostics_get_descriptor%published_fields(3)="uusg_total_local"
58  subgrid_profile_diagnostics_get_descriptor%published_fields(4)="vvsg_total_local"
59  subgrid_profile_diagnostics_get_descriptor%published_fields(5)="wwsg_total_local"
60  subgrid_profile_diagnostics_get_descriptor%published_fields(6)="tkesg_total_local"
61  subgrid_profile_diagnostics_get_descriptor%published_fields(7)="wtsg_total_local"
62  subgrid_profile_diagnostics_get_descriptor%published_fields(8)="th2sg_total_local"
63  subgrid_profile_diagnostics_get_descriptor%published_fields(9)="wqsg_total_local"
64 
65 ! =====================================================
66 ! 2nd, provisionally instantaneous, stream
67 
68  subgrid_profile_diagnostics_get_descriptor%published_fields(9+1)="i_uwsg_total_local"
69  subgrid_profile_diagnostics_get_descriptor%published_fields(9+2)="i_vwsg_total_local"
70  subgrid_profile_diagnostics_get_descriptor%published_fields(9+3)="i_uusg_total_local"
71  subgrid_profile_diagnostics_get_descriptor%published_fields(9+4)="i_vvsg_total_local"
72  subgrid_profile_diagnostics_get_descriptor%published_fields(9+5)="i_wwsg_total_local"
73  subgrid_profile_diagnostics_get_descriptor%published_fields(9+6)="i_tkesg_total_local"
74  subgrid_profile_diagnostics_get_descriptor%published_fields(9+7)="i_wtsg_total_local"
75  subgrid_profile_diagnostics_get_descriptor%published_fields(9+8)="i_th2sg_total_local"
76  subgrid_profile_diagnostics_get_descriptor%published_fields(9+9)="i_wqsg_total_local"
77 ! =====================================================
78 
Here is the call graph for this function:

◆ timestep_callback()

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

Definition at line 120 of file subgrid_profile_diagnostics.F90.

120  type(model_state_type), target, intent(inout) :: current_state
121 
122  integer :: k, i
123 
124  if (current_state%first_timestep_column) then
125  uwsg_tot(:) = 0.0_default_precision
126  vwsg_tot(:) = 0.0_default_precision
127  uusg_tot(:) = 0.0_default_precision
128  vvsg_tot(:) = 0.0_default_precision
129  wwsg_tot(:) = 0.0_default_precision
130  tkesg_tot(:) = 0.0_default_precision
131  wtsg_tot(:) = 0.0_default_precision
132  th2sg_tot(:) = 0.0_default_precision
133  wqsg_tot(:) = 0.0_default_precision
134  end if
135 
136  if (.not. current_state%halo_column) then
137 ! Subgrid diagnostics
138  do k=1, current_state%local_grid%size(z_index)-1
139 !
140 ! Field on kth rho-level, so gradient evaluated from k+1st and kth rhon-levels. Horizontally aligned with
141 ! w-points.
142  uwsg_tot(k) = uwsg_tot(k) - 0.5 * &
143  current_state%vis_coefficient%data(k,current_state%column_local_y,current_state%column_local_x-1) * &
144  ( current_state%u%data(k+1,current_state%column_local_y,current_state%column_local_x-1) - &
145  current_state%u%data(k,current_state%column_local_y,current_state%column_local_x-1) ) * &
146  current_state%global_grid%configuration%vertical%rdzn(k+1)
147  uwsg_tot(k) = uwsg_tot(k) - 0.5 * &
148  current_state%vis_coefficient%data(k,current_state%column_local_y,current_state%column_local_x) * &
149  ( current_state%u%data(k+1,current_state%column_local_y,current_state%column_local_x) - &
150  current_state%u%data(k,current_state%column_local_y,current_state%column_local_x) ) * &
151  current_state%global_grid%configuration%vertical%rdzn(k+1)
152 !
153 ! Field on kth rho-level, so gradient evaluated from k+1st and kth rhon-levels. Horizontally aligned with
154 ! w-points.
155  vwsg_tot(k) = vwsg_tot(k) - 0.5 * &
156  current_state%vis_coefficient%data(k,current_state%column_local_y-1,current_state%column_local_x) * &
157  ( current_state%v%data(k+1,current_state%column_local_y-1,current_state%column_local_x) - &
158  current_state%v%data(k,current_state%column_local_y-1,current_state%column_local_x) ) * &
159  current_state%global_grid%configuration%vertical%rdzn(k+1)
160  vwsg_tot(k) = vwsg_tot(k) - 0.5 * &
161  current_state%vis_coefficient%data(k,current_state%column_local_y,current_state%column_local_x) * &
162  ( current_state%v%data(k+1,current_state%column_local_y,current_state%column_local_x) - &
163  current_state%v%data(k,current_state%column_local_y,current_state%column_local_x) ) * &
164  current_state%global_grid%configuration%vertical%rdzn(k+1)
165  !
166  enddo
167  ! Field on kth rho-level, so gradient evaluated from k+1st and kth rhon-levels. Horizontally aligned with
168  ! w-points.
169  if (current_state%th%active) then
170  do k=1, current_state%local_grid%size(z_index)-1
171  wtsg_tot(k) = wtsg_tot(k) - &
172  current_state%diff_coefficient%data(k,current_state%column_local_y,current_state%column_local_x) * &
173  ( current_state%th%data(k+1,current_state%column_local_y,current_state%column_local_x) + &
174  current_state%global_grid%configuration%vertical%thref(k+1) - &
175  current_state%th%data(k,current_state%column_local_y,current_state%column_local_x) - &
176  current_state%global_grid%configuration%vertical%thref(k) ) * &
177  current_state%global_grid%configuration%vertical%rdzn(k+1)
178  !
179  enddo
180  endif
181 
182  if (current_state%th%active .and. .not. current_state%passive_q .and. current_state%number_q_fields .gt. 0) then
183 
184  do k=1, current_state%local_grid%size(z_index)-1
185  ! not coded yet
186  enddo
187  endif
188 
189 ! =======================================================
190 ! Calculation of subgrid diagnostics dependent on the dissipation.
191 !
192 ! Rationalize this with smagorinsky.
193  ri_crit = 0.25_default_precision
194 !
195  ssq=calculate_half_squared_strain_rate(current_state, current_state%u, current_state%v, current_state%w)
196  richardson_number=calculate_richardson_number(current_state, ssq, current_state%th, current_state%q)
197 !
198  do k=2, current_state%local_grid%size(z_index)-1
199  ! Mimic LEM: I think this is the square of the mixing length (Brown et al. 94, Eq 7)
200  elamr_sq(k) = 0.0
201  if ( ( &
202  current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x) &
203  > 0.0) .and. (richardson_number(k) < ri_crit) ) then
204  elamr_sq(k) = &
205  current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x) / &
206  sqrt( 1.0 - richardson_number(k) * &
207  current_state%diff_coefficient%data(k, current_state%column_local_y, current_state%column_local_x) / &
208  current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x) )
209  end if
210  !
211  ! This was called EPS in the LEM
212  dissipation(k) = ssq(k) * ( &
213  current_state%vis_coefficient%data(k, current_state%column_local_y, current_state%column_local_x) - &
214  richardson_number(k) * &
215  current_state%diff_coefficient%data(k, current_state%column_local_y, current_state%column_local_x) )
216  !
217  ! This constant needs to go somewhere accessible and where it can be set. The code in the LEM
218  ! seems to go round and round in circles here.
219  a2_n = 0.23
220  subgrid_tke(k) = ( dissipation(k) * dissipation(k) * elamr_sq(k) ) ** (1.0/3.0) / a2_n
221  !
222  ! Assume isotropy.
223  tkesg_tot(k) = tkesg_tot(k) + subgrid_tke(k)
224  uusg_tot(k) = uusg_tot(k) + (2.0/3.0) * subgrid_tke(k)
225  vvsg_tot(k) = vvsg_tot(k) + (2.0/3.0) * subgrid_tke(k)
226  wwsg_tot(k) = wwsg_tot(k) + (2.0/3.0) * subgrid_tke(k)
227  enddo
228 
229  !
230  ! Thermal equivalents:
231  ! Again, this needs to go somewhere better. pr_n is used in Smagorinsky anyway (as a local variable).
232 
233  if (current_state%th%active) then
234  epsth=calculate_thermal_dissipation_rate(current_state, current_state%th)
235  ath2_n = 0.3
236  pr_n = 0.7
237  do k=2, current_state%local_grid%size(z_index)-1
238  if (subgrid_tke(k) > 0.0) &
239  th2sg_tot(k) = th2sg_tot(k) + sqrt( a2_n * elamr_sq(k) / subgrid_tke(k) ) * &
240  epsth(k) / ( ath2_n**2 * pr_n)
241  enddo
242  endif
243 !
244 ! =======================================================
245  endif
Here is the caller graph for this function:

Variable Documentation

◆ a2_n

real(kind=default_precision) subgrid_profile_diagnostics_mod::a2_n
private

Definition at line 33 of file subgrid_profile_diagnostics.F90.

33  real(kind=DEFAULT_PRECISION) :: a2_n, ath2_n, pr_n, ri_crit

◆ ath2_n

real(kind=default_precision) subgrid_profile_diagnostics_mod::ath2_n
private

Definition at line 33 of file subgrid_profile_diagnostics.F90.

◆ dissipation

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::dissipation
private

Definition at line 29 of file subgrid_profile_diagnostics.F90.

29  real(kind=DEFAULT_PRECISION), dimension(:), allocatable :: &
30  dissipation, epsth, ssq, elamr_sq, richardson_number, &
31  subgrid_tke

◆ elamr_sq

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::elamr_sq
private

Definition at line 29 of file subgrid_profile_diagnostics.F90.

◆ epsth

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::epsth
private

Definition at line 29 of file subgrid_profile_diagnostics.F90.

◆ iql

integer subgrid_profile_diagnostics_mod::iql
private

Definition at line 22 of file subgrid_profile_diagnostics.F90.

◆ iqv

integer subgrid_profile_diagnostics_mod::iqv
private

Definition at line 22 of file subgrid_profile_diagnostics.F90.

◆ pr_n

real(kind=default_precision) subgrid_profile_diagnostics_mod::pr_n
private

Definition at line 33 of file subgrid_profile_diagnostics.F90.

◆ qlcrit

real(kind=default_precision) subgrid_profile_diagnostics_mod::qlcrit
private

Definition at line 34 of file subgrid_profile_diagnostics.F90.

34  real(kind=DEFAULT_PRECISION) :: qlcrit

◆ ri_crit

real(kind=default_precision) subgrid_profile_diagnostics_mod::ri_crit
private

Definition at line 33 of file subgrid_profile_diagnostics.F90.

◆ richardson_number

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::richardson_number
private

Definition at line 29 of file subgrid_profile_diagnostics.F90.

◆ ssq

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::ssq
private

Definition at line 29 of file subgrid_profile_diagnostics.F90.

◆ subgrid_tke

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::subgrid_tke
private

Definition at line 29 of file subgrid_profile_diagnostics.F90.

◆ th2sg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::th2sg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.

◆ tkesg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::tkesg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.

◆ total_points

integer subgrid_profile_diagnostics_mod::total_points
private

Definition at line 22 of file subgrid_profile_diagnostics.F90.

22  integer :: total_points, iqv, iql

◆ uusg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::uusg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.

◆ uwsg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::uwsg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.

24  real(kind=DEFAULT_PRECISION), dimension(:), allocatable :: &
25  uwsg_tot, vwsg_tot, uusg_tot, vvsg_tot, wwsg_tot, &
26  tkesg_tot, wtsg_tot, th2sg_tot, wqsg_tot

◆ vvsg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::vvsg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.

◆ vwsg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::vwsg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.

◆ wqsg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::wqsg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.

◆ wtsg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::wtsg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.

◆ wwsg_tot

real(kind=default_precision), dimension(:), allocatable subgrid_profile_diagnostics_mod::wwsg_tot
private

Definition at line 24 of file subgrid_profile_diagnostics.F90.