MONC
Functions/Subroutines | Variables
fftsolver_mod Module Reference

Pressure solver which uses a tridiagonal algorithm operating on the pressure terms in Fourier space. It uses the pencil FFT module for 3D FFTs in pencil decomposition. These use FFTW for the actual FFT kernel. More...

Functions/Subroutines

type(component_descriptor_type) function, public fftsolver_get_descriptor ()
 Descriptor of this component for registration. More...
 
subroutine initialisation_callback (current_state)
 This initialisation callback sets up the pencil fft module, allocates data for the fourier space pressure term (might be different size than p) and populates cos x and y. More...
 
subroutine timestep_callback (current_state)
 Timestep call back, which will transform to Fourier space, do a tridiagonal solve and then back into time space. More...
 
subroutine finalisation_callback (current_state)
 Called at MONC finalisation, will call to the pencil fft module to clean itself up and free the pressure term. More...
 
subroutine complete_psrce_calculation (current_state, y_halo_size, x_halo_size)
 Completes the psrce calculation by waiting on all outstanding psrce communications to complete and then combine the received values with the P field for U and V. More...
 
subroutine tridiagonal_solver (current_state, pressure_term, fourier_space_sizes)
 The tridiagonal solver which runs in Fourier space on the pressure terms. Note that because we are going from n reals to n/2+1 complex numbers (and into their reals for this solver) then there might be more data in the pressure term than in p. Therefore use the space sizes which are provided as an argument to this procedure rather than the current state local grid dimensions. More...
 
subroutine copy_p_to_halo_buffer (current_state, neighbour_description, dim, source_index, pid_location, current_page, source_data)
 Copies the p field data to halo buffers for a specific process in a dimension and halo cell. More...
 
subroutine copy_halo_buffer_to_p (current_state, neighbour_description, dim, target_index, neighbour_location, current_page, source_data)
 
subroutine perform_local_data_copy_for_p (current_state, halo_depth, involve_corners, source_data)
 Does local data copying for P variable halo swap. More...
 

Variables

real(kind=default_precision), dimension(:), allocatable cos_x
 
real(kind=default_precision), dimension(:), allocatable cos_y
 
real(kind=default_precision) pi
 
real(kind=default_precision), dimension(:,:,:), allocatable pt
 
integer, dimension(3) fourier_space_sizes
 
type(halo_communication_type), save halo_swap_state
 

Detailed Description

Pressure solver which uses a tridiagonal algorithm operating on the pressure terms in Fourier space. It uses the pencil FFT module for 3D FFTs in pencil decomposition. These use FFTW for the actual FFT kernel.

Function/Subroutine Documentation

◆ complete_psrce_calculation()

subroutine fftsolver_mod::complete_psrce_calculation ( type(model_state_type), intent(inout), target  current_state,
integer, intent(in)  y_halo_size,
integer, intent(in)  x_halo_size 
)
private

Completes the psrce calculation by waiting on all outstanding psrce communications to complete and then combine the received values with the P field for U and V.

Parameters
current_stateThe current model state
y_halo_sizeThe halo size in the Y dimension
x_halo_sizeThe halo size in the X dimension

Definition at line 144 of file fftsolver.F90.

145  type(model_state_type), target, intent(inout) :: current_state
146  integer, intent(in) :: y_halo_size, x_halo_size
147 
148  integer :: ierr, combined_handles(2), i, j, k
149 
150  combined_handles(1)=current_state%psrce_x_hs_recv_request
151  combined_handles(2)=current_state%psrce_y_hs_recv_request
152  call mpi_waitall(2, combined_handles, mpi_statuses_ignore, ierr)
153 
154  do j=current_state%local_grid%local_domain_start_index(y_index), current_state%local_grid%local_domain_end_index(y_index)
155  do k=2,current_state%local_grid%size(z_index)
156 #ifdef U_ACTIVE
157  current_state%p%data(k,j,x_halo_size+1)=current_state%p%data(k,j,x_halo_size+1)-&
158  current_state%psrce_recv_buffer_x(k-1,j-x_halo_size)
159 #endif
160 #ifdef V_ACTIVE
161  if (j .gt. y_halo_size+1) current_state%p%data(k, j, x_halo_size+1)=current_state%p%data(k, j, x_halo_size+1)-&
162  current_state%global_grid%configuration%horizontal%cy * current_state%sv%data(k, j-1, x_halo_size+1)
163 #endif
164  end do
165  end do
166 
167 #ifdef V_ACTIVE
168  do i=current_state%local_grid%local_domain_start_index(x_index), current_state%local_grid%local_domain_end_index(x_index)
169  do k=2,current_state%local_grid%size(z_index)
170  current_state%p%data(k,y_halo_size+1,i)=current_state%p%data(k,y_halo_size+1,i)-&
171  current_state%psrce_recv_buffer_y(k-1,i-y_halo_size)
172  end do
173  end do
174 #endif
175 
176  combined_handles(1)=current_state%psrce_x_hs_send_request
177  combined_handles(2)=current_state%psrce_y_hs_send_request
178  call mpi_waitall(2, combined_handles, mpi_statuses_ignore, ierr)
Here is the caller graph for this function:

◆ copy_halo_buffer_to_p()

subroutine fftsolver_mod::copy_halo_buffer_to_p ( 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

Definition at line 267 of file fftsolver.F90.

269  type(model_state_type), intent(inout) :: current_state
270  integer, intent(in) :: dim, target_index, neighbour_location
271  integer, intent(inout) :: current_page(:)
272  type(neighbour_description_type), intent(inout) :: neighbour_description
273  type(field_data_wrapper_type), dimension(:), intent(in), optional :: source_data
274 
275  call copy_buffer_to_field(current_state%local_grid, neighbour_description%recv_halo_buffer, current_state%p%data, &
276  dim, target_index, current_page(neighbour_location))
277 
278  current_page(neighbour_location)=current_page(neighbour_location)+1
Here is the caller graph for this function:

◆ copy_p_to_halo_buffer()

subroutine fftsolver_mod::copy_p_to_halo_buffer ( type(model_state_type), intent(inout)  current_state,
type(neighbour_description_type), intent(inout)  neighbour_description,
integer, intent(in)  dim,
integer, intent(in)  source_index,
integer, intent(in)  pid_location,
integer, dimension(:), intent(inout)  current_page,
type(field_data_wrapper_type), dimension(:), intent(in), optional  source_data 
)
private

Copies the p field data to halo buffers for a specific process in a dimension and halo cell.

Parameters
current_stateThe current model state
neighbour_descriptionsDescription of the neighbour halo swapping status
dimDimension to copy from
source_indexThe source index of the dimension we are reading from in the prognostic field
pid_locationLocation of the neighbouring process in the local stored data structures
current_pageThe current (next) buffer page to copy into
source_dataOptional source data which is read from

Definition at line 248 of file fftsolver.F90.

250  type(model_state_type), intent(inout) :: current_state
251  integer, intent(in) :: dim, pid_location, source_index
252  integer, intent(inout) :: current_page(:)
253  type(neighbour_description_type), intent(inout) :: neighbour_description
254  type(field_data_wrapper_type), dimension(:), intent(in), optional :: source_data
255 
256  call copy_field_to_buffer(current_state%local_grid, neighbour_description%send_halo_buffer, current_state%p%data, &
257  dim, source_index, current_page(pid_location))
258 
259  current_page(pid_location)=current_page(pid_location)+1
Here is the caller graph for this function:

◆ fftsolver_get_descriptor()

type(component_descriptor_type) function, public fftsolver_mod::fftsolver_get_descriptor

Descriptor of this component for registration.

Returns
The fft solver component descriptor

Definition at line 32 of file fftsolver.F90.

33  fftsolver_get_descriptor%name="fftsolver"
34  fftsolver_get_descriptor%version=0.1
35  fftsolver_get_descriptor%initialisation=>initialisation_callback
36  fftsolver_get_descriptor%timestep=>timestep_callback
37  fftsolver_get_descriptor%finalisation=>finalisation_callback
Here is the call graph for this function:
Here is the caller graph for this function:

◆ finalisation_callback()

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

Called at MONC finalisation, will call to the pencil fft module to clean itself up and free the pressure term.

Parameters
current_stateThe current model state

Definition at line 130 of file fftsolver.F90.

131  type(model_state_type), target, intent(inout) :: current_state
132 
133  call finalise_pencil_fft(current_state%parallel%monc_communicator)
134  deallocate(pt)
135  if (allocated(cos_x)) deallocate(cos_x)
136  if (allocated(cos_y)) deallocate(cos_y)
Here is the caller graph for this function:

◆ initialisation_callback()

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

This initialisation callback sets up the pencil fft module, allocates data for the fourier space pressure term (might be different size than p) and populates cos x and y.

Definition at line 42 of file fftsolver.F90.

43  type(model_state_type), target, intent(inout) :: current_state
44 
45  integer :: i, my_y_start, my_x_start
46 
47  if (.not. is_component_enabled(current_state%options_database, "diverr")) then
48  call log_master_log(log_error, "The FFT solver component requires the diverr component to be enabled")
49  end if
50 
51  pi=4.0_default_precision*atan(1.0_default_precision)
52 
53  fourier_space_sizes=initialise_pencil_fft(current_state, my_y_start, my_x_start)
54 
55  call init_halo_communication(current_state, get_single_field_per_halo_cell, halo_swap_state, 1, .false.)
56 
57  allocate(pt(fourier_space_sizes(z_index), fourier_space_sizes(y_index), fourier_space_sizes(x_index)))
58 
59 #ifdef U_ACTIVE
60  allocate(cos_x(fourier_space_sizes(x_index)))
61  do i=1, fourier_space_sizes(x_index)
62  cos_x(i)=(2.0_default_precision/(current_state%global_grid%configuration%horizontal%dx*&
63  current_state%global_grid%configuration%horizontal%dx))&
64  *(cos(2.0_default_precision*pi*real(((i-1)+(my_x_start-1))/2, kind=default_precision)/&
65  real(current_state%global_grid%size(X_INDEX), kind=default_precision))-1.0_default_precision)
66  end do
67 #endif
68 
69 #ifdef V_ACTIVE
70  allocate(cos_y(fourier_space_sizes(y_index)))
71  do i=1, fourier_space_sizes(y_index)
72  cos_y(i)=(2.0_default_precision/(current_state%global_grid%configuration%horizontal%dy*&
73  current_state%global_grid%configuration%horizontal%dy))&
74  *(cos(2.0_default_precision*pi*real(((i-1)+(my_y_start-1))/2, kind=default_precision)/&
75  real(current_state%global_grid%size(Y_INDEX), kind=default_precision))-1.0_default_precision)
76  end do
77 #endif
78  current_state%psrce_x_hs_send_request=mpi_request_null
79  current_state%psrce_y_hs_send_request=mpi_request_null
80  current_state%psrce_x_hs_recv_request=mpi_request_null
81  current_state%psrce_y_hs_recv_request=mpi_request_null
Here is the caller graph for this function:

◆ perform_local_data_copy_for_p()

subroutine fftsolver_mod::perform_local_data_copy_for_p ( 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 P variable halo swap.

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

Definition at line 284 of file fftsolver.F90.

285  type(model_state_type), intent(inout) :: current_state
286  integer, intent(in) :: halo_depth
287  logical, intent(in) :: involve_corners
288  type(field_data_wrapper_type), dimension(:), intent(in), optional :: source_data
289 
290  call perform_local_data_copy_for_field(current_state%p%data, current_state%local_grid, &
291  current_state%parallel%my_rank, halo_depth, involve_corners)
Here is the caller graph for this function:

◆ timestep_callback()

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

Timestep call back, which will transform to Fourier space, do a tridiagonal solve and then back into time space.

Parameters
current_stateThe current model state

Definition at line 86 of file fftsolver.F90.

87  type(model_state_type), target, intent(inout) :: current_state
88 
89  integer :: start_loc(3), end_loc(3), i
90 
91  do i=1,3
92  start_loc(i)=current_state%local_grid%local_domain_start_index(i)
93  end_loc(i)=current_state%local_grid%local_domain_end_index(i)
94  end do
95 
96  call complete_psrce_calculation(current_state, current_state%local_grid%halo_size(y_index), &
97  current_state%local_grid%halo_size(x_index))
98 
99 #ifdef FFT_TEST_MODE
100  current_state%p%data=real(current_state%parallel%my_rank, kind=8) + 1.d0
101 #endif
102 
103  call perform_forward_3dfft(current_state, current_state%p%data(start_loc(z_index):end_loc(z_index), &
104  start_loc(y_index):end_loc(y_index), start_loc(x_index):end_loc(x_index)), pt)
105 
106 #ifndef FFT_TEST_MODE
107  call tridiagonal_solver(current_state, pt, fourier_space_sizes)
108 #endif
109 
110  ! Here it is complex space, distributed as needed. The other option is real space but with +1 for the last process in Y
111  ! as require that complex number - not sure the best approach. We can extract the values here from complex anyway so
112  ! worth trying that first. Operating on the size of pt rather than grid sizes. Downside of real space xform is then we have +1
113  ! in the forwards transformation
114  call perform_backwards_3dfft(current_state, pt, current_state%p%data(start_loc(z_index):end_loc(z_index), &
115  start_loc(y_index):end_loc(y_index), start_loc(x_index):end_loc(x_index)))
116 
117 #ifdef FFT_TEST_MODE
118  if (current_state%parallel%my_rank == 1) then
119  write(*,*) current_state%parallel%my_rank, current_state%p%data(:,3,3)
120  end if
121 #endif
122 
123  call blocking_halo_swap(current_state, halo_swap_state, copy_p_to_halo_buffer, &
124  perform_local_data_copy_for_p, copy_halo_buffer_to_p)
125 
Here is the call graph for this function:
Here is the caller graph for this function:

◆ tridiagonal_solver()

subroutine fftsolver_mod::tridiagonal_solver ( type(model_state_type), intent(inout), target  current_state,
real(kind=default_precision), dimension(:,:,:), intent(inout)  pressure_term,
integer, dimension(3), intent(in)  fourier_space_sizes 
)
private

The tridiagonal solver which runs in Fourier space on the pressure terms. Note that because we are going from n reals to n/2+1 complex numbers (and into their reals for this solver) then there might be more data in the pressure term than in p. Therefore use the space sizes which are provided as an argument to this procedure rather than the current state local grid dimensions.

Parameters
current_stateThe current model state
pressure_termThe pressure term in Fourier space
fourier_space_sizesThe size of the pressure term in each dimension

Definition at line 188 of file fftsolver.F90.

189  type(model_state_type), target, intent(inout) :: current_state
190  real(kind=default_precision), dimension(:,:,:), intent(inout) :: pressure_term
191  integer, intent(in) :: fourier_space_sizes(3)
192 
193  integer :: i, j, k, j_start
194  real(kind=default_precision) :: b(fourier_space_sizes(z_index)), b1(fourier_space_sizes(z_index)), &
195  s(fourier_space_sizes(z_index)), s1(fourier_space_sizes(z_index)), cij
196 
197  do i=1,fourier_space_sizes(x_index)
198  j_start=merge(3, 1, current_state%local_grid%start(y_index) ==1 .and. current_state%local_grid%start(x_index) == 1 &
199  .and. i .lt. 3)
200  do j=j_start,fourier_space_sizes(y_index)
201 
202  cij=cos_x(i)+cos_y(j)
203  b(2)=cij-current_state%global_grid%configuration%vertical%cza(2)
204  b1(2)=1.0_default_precision/b(2)
205  s1(2)=pressure_term(2,j,i)
206 
207  do k=3,fourier_space_sizes(z_index)
208  b(k)=cij+current_state%global_grid%configuration%vertical%czg(k)
209  b1(k)=1.0_default_precision/(b(k)-current_state%global_grid%configuration%vertical%czh(k)*b1(k-1))
210  s1(k)=pressure_term(k,j,i)-current_state%global_grid%configuration%vertical%czb(k)*s1(k-1)*b1(k-1)
211  end do
212 
213  pressure_term(fourier_space_sizes(z_index),j,i)=s1(fourier_space_sizes(z_index))* b1(fourier_space_sizes(z_index))
214 
215  do k=fourier_space_sizes(z_index)-1,2,-1
216  pressure_term(k,j,i)=(s1(k)-current_state%global_grid%configuration%vertical%cza(k)*&
217  pressure_term(k+1,j,i))*b1(k)
218  end do
219  end do
220  end do
221 
222  ! Handle the zero wavenumber, which will only be on processes where the X and Y dimension starts at 1
223  if (current_state%local_grid%start(y_index) == 1 .and. current_state%local_grid%start(x_index) == 1) then
224  do i=1,2
225  do j=1,2
226  s(2)=pressure_term(2,j,i)
227  pressure_term(1,j,i)=0.0_default_precision
228  pressure_term(2,j,i)=0.0_default_precision
229  do k=3, fourier_space_sizes(z_index)
230  s(k)=pressure_term(k,j,i)
231  pressure_term(k,j,i)=(s(k-1)-current_state%global_grid%configuration%vertical%czg(k-1)*pressure_term(k-1,j,i)-&
232  current_state%global_grid%configuration%vertical%czb(k-1)*pressure_term(k-2,j,i))/&
233  current_state%global_grid%configuration%vertical%cza(k-1)
234  end do
235  end do
236  end do
237  end if
Here is the caller graph for this function:

Variable Documentation

◆ cos_x

real(kind=default_precision), dimension(:), allocatable fftsolver_mod::cos_x
private

Definition at line 21 of file fftsolver.F90.

21  real(kind=default_precision), dimension(:), allocatable :: cos_x, cos_y

◆ cos_y

real(kind=default_precision), dimension(:), allocatable fftsolver_mod::cos_y
private

Definition at line 21 of file fftsolver.F90.

◆ fourier_space_sizes

integer, dimension(3) fftsolver_mod::fourier_space_sizes
private

Definition at line 24 of file fftsolver.F90.

24  integer :: fourier_space_sizes(3)

◆ halo_swap_state

type(halo_communication_type), save fftsolver_mod::halo_swap_state
private

Definition at line 25 of file fftsolver.F90.

25  type(halo_communication_type), save :: halo_swap_state

◆ pi

real(kind=default_precision) fftsolver_mod::pi
private

Definition at line 22 of file fftsolver.F90.

22  real(kind=default_precision) :: pi

◆ pt

real(kind=default_precision), dimension(:,:,:), allocatable fftsolver_mod::pt
private

Definition at line 23 of file fftsolver.F90.

23  real(kind=default_precision), dimension(:,:,:), allocatable :: pt
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47
science_constants_mod::pi
real(kind=default_precision), public pi
Definition: scienceconstants.F90:13
datadefn_mod::default_precision
integer, parameter, public default_precision
MPI communication type which we use for the prognostic and calculation data.
Definition: datadefn.F90:17