MONC
Functions/Subroutines | Variables
diffusion_mod Module Reference

Diffusion on the TH and Q fields. More...

Functions/Subroutines

type(component_descriptor_type) function, public diffusion_get_descriptor ()
 Provides the descriptor back to the caller and is used in component registration. More...
 
subroutine field_information_retrieval_callback (current_state, name, field_information)
 Field information retrieval callback, this returns information for a specific components published field. More...
 
subroutine field_value_retrieval_callback (current_state, name, field_value)
 Field value retrieval callback, this returns the value of a specific published field. More...
 
subroutine initialisation_callback (current_state)
 Sets up the stencil_mod (used in interpolation) and allocates data for the flux fields. More...
 
subroutine finalisation_callback (current_state)
 
subroutine timestep_callback (current_state)
 At each timestep will compute the diffusion source terms for TH and Q fields per column if these fields are active. More...
 
subroutine perform_q_diffusion (current_state, local_y, local_x)
 Computes the diffusion source terms for each Q field. More...
 
subroutine perform_th_diffusion (current_state, local_y, local_x)
 Computes the diffusion source terms for the theta field. More...
 
subroutine general_diffusion (current_state, field, source_field, local_y, local_x, diagnostics)
 General diffusion computation for any field which is provided as arguments. Works in a column. More...
 
subroutine perform_local_data_copy_for_diff (current_state, halo_depth, involve_corners, source_data)
 Does local data copying for diffusion coefficient variable halo swap. More...
 
subroutine copy_halo_buffer_to_diff (current_state, neighbour_description, dim, target_index, neighbour_location, current_page, source_data)
 Copies the halo buffer to halo location for the diffusion coefficient field. More...
 
subroutine copy_halo_buffer_to_diff_corners (current_state, neighbour_description, corner_loc, x_target_index, y_target_index, neighbour_location, current_page, source_data)
 Copies the corner halo buffer to the diffusion coefficient field corners. More...
 

Variables

real(kind=default_precision), dimension(:), allocatable th_diffusion
 
real(kind=default_precision), dimension(:,:), allocatable q_diffusion
 

Detailed Description

Diffusion on the TH and Q fields.

Function/Subroutine Documentation

◆ copy_halo_buffer_to_diff()

subroutine diffusion_mod::copy_halo_buffer_to_diff ( type(model_state_type), intent(inout)  current_state,
type(neighbour_description_type), intent(inout)  neighbour_description,
integer, intent(in)  dim,
integer, intent(in)  target_index,
integer, intent(in)  neighbour_location,
integer, dimension(:), intent(inout)  current_page,
type(field_data_wrapper_type), dimension(:), intent(in), optional  source_data 
)
private

Copies the halo buffer to halo location for the diffusion coefficient field.

Parameters
current_stateThe current model state
neighbour_descriptionThe halo swapping description of the neighbour we are accessing the buffer of
dimThe dimension we receive for
target_indexThe target index for the dimension we are receiving for
neighbour_locationThe location in the local neighbour data stores of this neighbour
current_pageThe current, next, halo swap page to read from (all previous have been read and copied already)
source_dataOptional source data which is written into

Definition at line 244 of file diffusion.F90.

244  type(model_state_type), intent(inout) :: current_state
245  integer, intent(in) :: dim, target_index, neighbour_location
246  integer, intent(inout) :: current_page(:)
247  type(neighbour_description_type), intent(inout) :: neighbour_description
248  type(field_data_wrapper_type), dimension(:), intent(in), optional :: source_data
249 
250  call copy_buffer_to_field(current_state%local_grid, neighbour_description%recv_halo_buffer, &
251  current_state%diff_coefficient%data, dim, target_index, current_page(neighbour_location))
252 
253  current_page(neighbour_location)=current_page(neighbour_location)+1
Here is the caller graph for this function:

◆ copy_halo_buffer_to_diff_corners()

subroutine diffusion_mod::copy_halo_buffer_to_diff_corners ( type(model_state_type), intent(inout)  current_state,
type(neighbour_description_type), intent(inout)  neighbour_description,
integer, intent(in)  corner_loc,
integer, intent(in)  x_target_index,
integer, intent(in)  y_target_index,
integer, intent(in)  neighbour_location,
integer, dimension(:), intent(inout)  current_page,
type(field_data_wrapper_type), dimension(:), intent(in), optional  source_data 
)
private

Copies the corner halo buffer to the diffusion coefficient field corners.

Parameters
current_stateThe current model state
neighbour_descriptionThe halo swapping description of the neighbour we are accessing the buffer of
corner_locThe corner location
x_target_indexThe X target index for the dimension we are receiving for
y_target_indexThe Y target index for the dimension we are receiving for
neighbour_locationThe location in the local neighbour data stores of this neighbour
current_pageThe current, next, halo swap page to read from (all previous have been read and copied already)
source_dataOptional source data which is written into

Definition at line 267 of file diffusion.F90.

267  type(model_state_type), intent(inout) :: current_state
268  integer, intent(in) :: corner_loc, x_target_index, y_target_index, neighbour_location
269  integer, intent(inout) :: current_page(:)
270  type(neighbour_description_type), intent(inout) :: neighbour_description
271  type(field_data_wrapper_type), dimension(:), intent(in), optional :: source_data
272 
273  call copy_buffer_to_corner(current_state%local_grid, neighbour_description%recv_corner_buffer, &
274  current_state%diff_coefficient%data, corner_loc, x_target_index, y_target_index, current_page(neighbour_location))
275 
276  current_page(neighbour_location)=current_page(neighbour_location)+1
Here is the caller graph for this function:

◆ diffusion_get_descriptor()

type(component_descriptor_type) function, public diffusion_mod::diffusion_get_descriptor ( )

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

Returns
The termination check component descriptor

Definition at line 30 of file diffusion.F90.

30  diffusion_get_descriptor%name="diffusion"
31  diffusion_get_descriptor%version=0.1
32  diffusion_get_descriptor%initialisation=>initialisation_callback
33  diffusion_get_descriptor%timestep=>timestep_callback
34  diffusion_get_descriptor%finalisation=>finalisation_callback
35 
36  diffusion_get_descriptor%field_value_retrieval=>field_value_retrieval_callback
37  diffusion_get_descriptor%field_information_retrieval=>field_information_retrieval_callback
38  allocate(diffusion_get_descriptor%published_fields(2))
39  diffusion_get_descriptor%published_fields(1)="th_diffusion"
40  diffusion_get_descriptor%published_fields(2)="q_diffusion"
Here is the call graph for this function:

◆ field_information_retrieval_callback()

subroutine diffusion_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 48 of file diffusion.F90.

48  type(model_state_type), target, intent(inout) :: current_state
49  character(len=*), intent(in) :: name
50  type(component_field_information_type), intent(out) :: field_information
51 
52  ! Field description is the same regardless of the specific field being retrieved
53  field_information%field_type=component_array_field_type
54  field_information%data_type=component_double_data_type
55  if (name .eq. "q_diffusion") then
56  field_information%number_dimensions=2
57  else
58  field_information%number_dimensions=1
59  end if
60  field_information%dimension_sizes(1)=current_state%local_grid%size(z_index)
61  if (name .eq. "q_diffusion") field_information%dimension_sizes(2)=current_state%number_q_fields
62  field_information%enabled=.true.
Here is the caller graph for this function:

◆ field_value_retrieval_callback()

subroutine diffusion_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 70 of file diffusion.F90.

70  type(model_state_type), target, intent(inout) :: current_state
71  character(len=*), intent(in) :: name
72  type(component_field_value_type), intent(out) :: field_value
73 
74  if (name .eq. "th_diffusion") then
75  allocate(field_value%real_1d_array(size(th_diffusion)), source=th_diffusion)
76  else if (name .eq. "q_diffusion") then
77  allocate(field_value%real_2d_array(size(q_diffusion, 1), size(q_diffusion, 2)), source=q_diffusion)
78  end if
Here is the caller graph for this function:

◆ finalisation_callback()

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

Definition at line 100 of file diffusion.F90.

100  type(model_state_type), target, intent(inout) :: current_state
101 
102  if (allocated(th_diffusion)) deallocate(th_diffusion)
103  if (allocated(q_diffusion)) deallocate(q_diffusion)
Here is the caller graph for this function:

◆ general_diffusion()

subroutine diffusion_mod::general_diffusion ( type(model_state_type), intent(inout), target  current_state,
type(prognostic_field_type), intent(inout)  field,
type(prognostic_field_type), intent(inout)  source_field,
integer, intent(in)  local_y,
integer, intent(in)  local_x,
real(kind=default_precision), dimension(:), intent(inout), optional  diagnostics 
)
private

General diffusion computation for any field which is provided as arguments. Works in a column.

Parameters
current_stateThe current model state
fieldThe field to take values from, typically zth or zq(n)
source_fieldThe source target field to update, typically sth or sq(n)
local_yLocal Y index
local_xLocal X index

Definition at line 176 of file diffusion.F90.

176  type(model_state_type), target, intent(inout) :: current_state
177  type(prognostic_field_type), intent(inout) :: field, source_field
178  integer, intent(in) :: local_y, local_x
179  real(kind=DEFAULT_PRECISION), dimension(:), intent(inout), optional :: diagnostics
180 
181  real(kind=DEFAULT_PRECISION) :: term
182  integer :: k
183 
184  do k=2, current_state%local_grid%size(z_index)
185  term=current_state%global_grid%configuration%horizontal%cx2*0.25_default_precision*&
186  (((current_state%diff_coefficient%data(k, local_y, local_x)+&
187  current_state%diff_coefficient%data(k, local_y, local_x-1))+&
188  (current_state%diff_coefficient%data(k-1, local_y, local_x)+&
189  current_state%diff_coefficient%data(k-1, local_y, local_x-1)))&
190  *(field%data(k, local_y, local_x-1)-field%data(k, local_y, local_x)) -&
191  ((current_state%diff_coefficient%data(k, local_y, local_x+1)+&
192  current_state%diff_coefficient%data(k, local_y, local_x))+&
193  (current_state%diff_coefficient%data(k-1, local_y, local_x+1)+&
194  current_state%diff_coefficient%data(k-1, local_y, local_x)))&
195  *(field%data(k, local_y, local_x)-field%data(k, local_y, local_x+1)) )&
196  +current_state%global_grid%configuration%horizontal%cy2*0.25_default_precision*(&
197  ((current_state%diff_coefficient%data(k, local_y, local_x)+&
198  current_state%diff_coefficient%data(k, local_y-1, local_x))+&
199  (current_state%diff_coefficient%data(k-1, local_y, local_x)+&
200  current_state%diff_coefficient%data(k-1, local_y-1, local_x)))&
201  *(field%data(k, local_y-1, local_x)-field%data(k, local_y, local_x)) -&
202  ((current_state%diff_coefficient%data(k, local_y+1, local_x)+&
203  current_state%diff_coefficient%data(k, local_y, local_x))+&
204  (current_state%diff_coefficient%data(k-1, local_y+1, local_x)+&
205  current_state%diff_coefficient%data(k-1, local_y, local_x)))&
206  *(field%data(k, local_y, local_x)-field%data(k, local_y+1, local_x)) )&
207  +( current_state%global_grid%configuration%vertical%czb(k)*&
208  current_state%diff_coefficient%data(k-1, local_y, local_x)*&
209  (field%data(k-1, local_y, local_x)-field%data(k, local_y, local_x)))
210 
211  if (k .lt. current_state%local_grid%size(z_index)) then
212  term=term - current_state%global_grid%configuration%vertical%cza(k)*&
213  current_state%diff_coefficient%data(k, local_y, local_x)*&
214  (field%data(k, local_y, local_x)-field%data(k+1, local_y, local_x))
215  end if
216  source_field%data(k, local_y, local_x)=source_field%data(k, local_y, local_x)+term
217  if (present(diagnostics)) diagnostics(k)=term
218  end do
Here is the caller graph for this function:

◆ initialisation_callback()

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

Sets up the stencil_mod (used in interpolation) and allocates data for the flux fields.

Parameters
current_stateThe current model state_mod

Definition at line 84 of file diffusion.F90.

84  type(model_state_type), target, intent(inout) :: current_state
85 
86  integer :: z_size, y_size, x_size
87 
88  z_size=current_state%local_grid%size(z_index) + current_state%local_grid%halo_size(z_index) * 2
89  y_size=current_state%local_grid%size(y_index) + current_state%local_grid%halo_size(y_index) * 2
90  x_size=current_state%local_grid%size(x_index) + current_state%local_grid%halo_size(x_index) * 2
91  allocate(current_state%diff_coefficient%data(z_size, y_size, x_size))
92 
93  z_size=current_state%global_grid%size(z_index)
94  allocate(th_diffusion(z_size))
95  allocate(q_diffusion(z_size, current_state%number_q_fields))
96 
Here is the caller graph for this function:

◆ perform_local_data_copy_for_diff()

subroutine diffusion_mod::perform_local_data_copy_for_diff ( type(model_state_type), intent(inout)  current_state,
integer, intent(in)  halo_depth,
logical, intent(in)  involve_corners,
type(field_data_wrapper_type), dimension(:), intent(in), optional  source_data 
)
private

Does local data copying for diffusion coefficient variable halo swap.

Parameters
current_stateThe current model state_mod
source_dataOptional source data which is written into

Definition at line 225 of file diffusion.F90.

225  type(model_state_type), intent(inout) :: current_state
226  integer, intent(in) :: halo_depth
227  logical, intent(in) :: involve_corners
228  type(field_data_wrapper_type), dimension(:), intent(in), optional :: source_data
229 
230  call perform_local_data_copy_for_field(current_state%diff_coefficient%data, current_state%local_grid, &
231  current_state%parallel%my_rank, halo_depth, involve_corners)
Here is the caller graph for this function:

◆ perform_q_diffusion()

subroutine diffusion_mod::perform_q_diffusion ( type(model_state_type), intent(inout), target  current_state,
integer, intent(in)  local_y,
integer, intent(in)  local_x 
)
private

Computes the diffusion source terms for each Q field.

Parameters
current_stateThe current model state
local_yLocal Y index
local_xLocal X index

Definition at line 132 of file diffusion.F90.

132  type(model_state_type), target, intent(inout) :: current_state
133  integer, intent(in) :: local_y, local_x
134 
135  integer :: n
136 
137  do n=1, current_state%number_q_fields
138  call general_diffusion(current_state, current_state%zq(n), current_state%sq(n), local_y, local_x, q_diffusion(:,n))
139  end do
Here is the call graph for this function:
Here is the caller graph for this function:

◆ perform_th_diffusion()

subroutine diffusion_mod::perform_th_diffusion ( type(model_state_type), intent(inout), target  current_state,
integer, intent(in)  local_y,
integer, intent(in)  local_x 
)
private

Computes the diffusion source terms for the theta field.

Parameters
current_stateThe current model state
local_yLocal Y index
local_xLocal X index

Definition at line 147 of file diffusion.F90.

147  type(model_state_type), target, intent(inout) :: current_state
148  integer, intent(in) :: local_y, local_x
149 
150  integer :: k
151  real(kind=DEFAULT_PRECISION) :: adjustment
152 
153  call general_diffusion(current_state, current_state%zth, current_state%sth, local_y, local_x, th_diffusion)
154 
155  if (current_state%use_anelastic_equations) then
156  ! This code only needs to be executed if anelastic, otherwise THREF is constant and the increment calculated here is zero
157  do k=2, current_state%local_grid%size(z_index)
158  adjustment=(current_state%global_grid%configuration%vertical%cza(k)*&
159  current_state%global_grid%configuration%vertical%dthref(k)*&
160  current_state%diff_coefficient%data(k, local_y, local_x) - current_state%global_grid%configuration%vertical%czb(k)*&
161  current_state%global_grid%configuration%vertical%dthref(k-1)*&
162  current_state%diff_coefficient%data(k-1, local_y, local_x))
163  current_state%sth%data(k, local_y, local_x)=current_state%sth%data(k, local_y, local_x)+adjustment
164  th_diffusion(k)=th_diffusion(k)+adjustment
165  end do
166  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ timestep_callback()

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

At each timestep will compute the diffusion source terms for TH and Q fields per column if these fields are active.

Parameters
current_stateThe current model state

Definition at line 109 of file diffusion.F90.

109  type(model_state_type), target, intent(inout) :: current_state
110 
111  integer :: local_y, local_x
112 
113  if (.not. current_state%use_viscosity_and_diffusion .or. current_state%halo_column) return
114  if (current_state%diffusion_halo_swap_state%swap_in_progress) then
115  ! If there is a diffusion halo swap in progress then complete it
116  call complete_nonblocking_halo_swap(current_state, current_state%diffusion_halo_swap_state, &
117  perform_local_data_copy_for_diff, copy_halo_buffer_to_diff, copy_halo_buffer_to_diff_corners)
118  end if
119 
120  local_y=current_state%column_local_y
121  local_x=current_state%column_local_x
122 
123  if (current_state%th%active) call perform_th_diffusion(current_state, local_y, local_x)
124  if (current_state%number_q_fields .gt. 0) call perform_q_diffusion(current_state, local_y, local_x)
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ q_diffusion

real(kind=default_precision), dimension(:,:), allocatable diffusion_mod::q_diffusion
private

Definition at line 21 of file diffusion.F90.

21  real(kind=DEFAULT_PRECISION), dimension(:,:), allocatable :: q_diffusion

◆ th_diffusion

real(kind=default_precision), dimension(:), allocatable diffusion_mod::th_diffusion
private

Definition at line 20 of file diffusion.F90.

20  real(kind=DEFAULT_PRECISION), dimension(:), allocatable :: th_diffusion