MONC
Data Types | Functions/Subroutines | Variables
mpi_communication_mod Module Reference

Abstraction layer around MPI, this issues and marshals the lower level communication details. More...

Data Types

interface  usleep
 

Functions/Subroutines

subroutine, public initialise_mpi_communication (provided_threading)
 Initialises MPI communication. More...
 
subroutine, public lock_mpi ()
 If we are explicitly managing MPI thread safety (SERIALIZED mode) then locks MPI. More...
 
subroutine, public unlock_mpi ()
 If we are explicitly managing MPI thread safety (SERIALIZED mode) then unlocks MPI. More...
 
subroutine, public pause_for_mpi_interleaving ()
 Pauses for a specific number of ms to allow for MPI interleaving, this is to avoid starvation. More...
 
subroutine, public wait_for_mpi_request (request, status)
 Waits for a specific MPI request to complete, either by managing thread safety and interleaving or just a call to MPI if we are in multiple mode. More...
 
subroutine, public waitall_for_mpi_requests (requests, count)
 Waits for all MPI requests to complete, either by managing thread safety and interleaving or just a call to MPI if we are in multiple mode. More...
 
integer function, public get_number_io_servers (io_comm)
 Retrieves the number of IO servers that are running in total. More...
 
integer function, public get_my_io_rank (io_comm)
 Retrieves my IO server rank out of the number of IO servers that are running. More...
 
subroutine, public register_command_receive ()
 Registers a request for receiving a command from any MONC process on the command channel. More...
 
integer function, public data_receive (mpi_datatype, num_elements, source, dump_data, data_dump_id, description_data)
 Awaits some data on the data channel. This is of the type, size from the source provided and can either be written into a byte buffer or integer buffer depending upon the arguments provided. More...
 
subroutine, public cancel_requests ()
 Cancels all outstanding communication requests. More...
 
subroutine cancel_request (req)
 Cancels a specific communication request. More...
 
logical function, public test_for_command (command, source)
 Tests for a command message based upon the request already registered. More...
 
logical function, public test_for_inter_io (inter_io_communications, number_of_inter_io, io_communicator, command, source, data_buffer)
 Tests for inter IO server communication. More...
 
subroutine, public free_mpi_type (the_type)
 Frees an MPI type, used in clean up. More...
 
integer function, public build_mpi_datatype (data_definition, data_size_info, data_size, field_start_locations, field_end_locations, field_dimensions)
 Builds the MPI type that corresponds to the data which will be received from a specific MONC process. Two factors determine the structure and size of this - the XML configuration which has been parsed and also specific details of array sizes sent by each process as part of its registration process. More...
 

Variables

integer, parameter ms_wait_between_tests =100
 Interface to the C usleep Linux call which allows us to sleep for a specific number of MS. More...
 
integer command_buffer
 Buffer used to receive the command data into when it arrives on that channel. More...
 
integer command_request_handle
 Request handle representing the asynchronous P2P command request. More...
 
integer mpi_threading_mode
 
integer, volatile mpi_mutex
 
logical manage_mpi_thread_safety
 

Detailed Description

Abstraction layer around MPI, this issues and marshals the lower level communication details.

Function/Subroutine Documentation

◆ build_mpi_datatype()

integer function, public mpi_communication_mod::build_mpi_datatype ( type(io_configuration_data_definition_type), intent(in)  data_definition,
type(data_sizing_description_type), dimension(:), intent(in)  data_size_info,
integer, intent(out)  data_size,
type(map_type), intent(out)  field_start_locations,
type(map_type), intent(out)  field_end_locations,
type(map_type), intent(out), optional  field_dimensions 
)

Builds the MPI type that corresponds to the data which will be received from a specific MONC process. Two factors determine the structure and size of this - the XML configuration which has been parsed and also specific details of array sizes sent by each process as part of its registration process.

Parameters
io_configurationIO server representation of the configuration which contains data structure layout
array_sizesSizes of each data array which has been received from a MONC process when it registeres
data_sizeThe data size corresponding to this type is returned (i.e. the buffer size in bytes required to hold it)
field_start_locationsFor the MONC process the start location for each field, keyed on field name
field_end_locationsFor the MONC process the end location for each field, keyed on field name
field_dimensionsOptional map of dimensions, if provided will store the number of dimensions for each field
Returns
The MPI data type representation

Definition at line 291 of file mpicommunication.F90.

293  type(io_configuration_data_definition_type), intent(in) :: data_definition
294  type(data_sizing_description_type), dimension(:), intent(in) :: data_size_info
295  integer, intent(out) :: data_size
296  type(map_type), intent(out) :: field_start_locations, field_end_locations
297  type(map_type), intent(out), optional :: field_dimensions
298 
299  integer :: type_extents(5), type_counts, i, j, field_start, data_type, field_array_sizes, &
300  temp_size, prev_data_type, old_types(20), offsets(20), block_counts(20), new_type, current_location, ierr, field_ignores
301  logical :: field_found
302  type(data_sizing_description_type) :: field_size_info
303 
304  type_extents=populate_mpi_type_extents()
305 
306  field_start=1
307  data_type=0
308  type_counts=0
309  field_array_sizes=0
310  field_ignores=0
311  current_location=1
312  do i=1,data_definition%number_of_data_fields
313  if (data_type == 0) then
314  prev_data_type=data_type
315  data_type=data_definition%fields(i)%data_type
316  else
317  if (data_type .ne. data_definition%fields(i)%data_type) then
318  ! For efficient type packing, combine multiple fields with the same type - therefore when the type changes work the previous one pack
319  call append_mpi_datatype(field_start, i-1-field_ignores, field_array_sizes, data_type, &
320  type_extents, prev_data_type, type_counts+1, old_types, offsets, block_counts)
321  field_start=i
322  field_array_sizes=0
323  field_ignores=0
324  prev_data_type=data_type
325  data_type=data_definition%fields(i)%data_type
326  type_counts=type_counts+1
327  end if
328  end if
329  call c_put_integer(field_start_locations, data_definition%fields(i)%name, current_location)
330  if (data_definition%fields(i)%field_type .eq. array_field_type .or. &
331  data_definition%fields(i)%field_type .eq. map_field_type) then
332  ! Grab the field info based upon the field name
333  field_found=get_data_description_from_name(data_size_info, data_definition%fields(i)%name, field_size_info)
334  if (.not. field_found .or. field_size_info%dimensions == 0) then
335  ! If no field info, or the dimension is 0 then this MONC process is not sending that field - check it is optional
336  if (.not. data_definition%fields(i)%optional) then
337  call log_log(log_error, "Non optional field `"//trim(data_definition%fields(i)%name)//&
338  "' omitted from MONC IO server registration")
339  end if
340  field_ignores=field_ignores+1
341  else
342  ! If the field is specified then use the size data to assemble the field size and append to current size
343  temp_size=1
344  do j=1, field_size_info%dimensions
345  temp_size=temp_size*field_size_info%dim_sizes(j)
346  end do
347  if (data_definition%fields(i)%field_type .eq. map_field_type) then
348  field_array_sizes=(field_array_sizes+temp_size*string_length*2)-1
349  current_location=current_location+temp_size*string_length*2
350  else
351  field_array_sizes=(field_array_sizes+temp_size)-1
352  current_location=current_location+temp_size*type_extents(data_type)
353  end if
354  end if
355  else
356  if (data_definition%fields(i)%optional) then
357  if (get_data_description_from_name(data_size_info, data_definition%fields(i)%name)) then
358  if (data_type==string_data_type) then
359  field_array_sizes=(field_array_sizes+string_length)-1
360  current_location=current_location+type_extents(data_type)*string_length
361  else
362  current_location=current_location+type_extents(data_type)
363  end if
364  else
365  field_ignores=field_ignores+1
366  end if
367  else
368  if (data_type==string_data_type) then
369  field_array_sizes=(field_array_sizes+string_length)-1
370  current_location=current_location+type_extents(data_type)*string_length
371  else
372  current_location=current_location+type_extents(data_type)
373  end if
374  end if
375  end if
376  call c_put_integer(field_end_locations, data_definition%fields(i)%name, current_location-1)
377  if (present(field_dimensions)) then
378  call c_put_integer(field_dimensions, data_definition%fields(i)%name, field_size_info%dimensions)
379  end if
380  end do
381  if (field_start .le. i-1) then
382  ! If there are outstanding fields to process then we do this here
383  call append_mpi_datatype(field_start, i-1, field_array_sizes, data_type, &
384  type_extents, prev_data_type, type_counts+1, old_types, offsets, block_counts)
385  type_counts=type_counts+1
386  end if
387  call lock_mpi()
388  call mpi_type_struct(type_counts, block_counts, offsets, old_types, new_type, ierr)
389  call mpi_type_commit(new_type, ierr)
390  call unlock_mpi()
391  call mpi_type_size(new_type, data_size, ierr)
392  build_mpi_datatype=new_type
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cancel_request()

subroutine mpi_communication_mod::cancel_request ( integer, intent(in)  req)
private

Cancels a specific communication request.

Parameters
reqHandle of the request to cancel

Definition at line 202 of file mpicommunication.F90.

203  integer, intent(in) :: req
204 
205  integer :: ierr
206 
207  if (req .ne. mpi_request_null) then
208  call lock_mpi()
209  call mpi_cancel(req, ierr)
210  call unlock_mpi()
211  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cancel_requests()

subroutine, public mpi_communication_mod::cancel_requests

Cancels all outstanding communication requests.

Definition at line 196 of file mpicommunication.F90.

197  call cancel_request(command_request_handle)
Here is the call graph for this function:
Here is the caller graph for this function:

◆ data_receive()

integer function, public mpi_communication_mod::data_receive ( integer, intent(in)  mpi_datatype,
integer, intent(in)  num_elements,
integer, intent(in)  source,
character, dimension(:), intent(inout), optional, allocatable  dump_data,
integer, intent(in), optional  data_dump_id,
type(data_sizing_description_type), dimension(:), intent(inout), optional  description_data 
)

Awaits some data on the data channel. This is of the type, size from the source provided and can either be written into a byte buffer or integer buffer depending upon the arguments provided.

Parameters
mpi_datatypeThe MPI type of the data we are receiving
sizeNumber of elements to receive
sourceThe PID of the MONC process to receieve this data from
dump_data(Optional) byte data buffer, for the data dump
description_data(Optional) integer data buffer, for data description

Definition at line 165 of file mpicommunication.F90.

166  integer, intent(in) :: mpi_datatype, num_elements, source
167  integer, intent(in), optional :: data_dump_id
168  character, dimension(:), allocatable, intent(inout), optional :: dump_data
169  type(data_sizing_description_type), dimension(:), intent(inout), optional :: description_data
170  integer :: ierr, request, status(MPI_STATUS_SIZE), recv_count, tag_to_use
171 
172  if (present(dump_data)) then
173  tag_to_use=data_tag
174  if (present(data_dump_id)) tag_to_use=tag_to_use+data_dump_id
175  call lock_mpi()
176  call mpi_irecv(dump_data, num_elements, mpi_datatype, source, tag_to_use, mpi_comm_world, request, ierr)
177  call unlock_mpi()
178  call wait_for_mpi_request(request, status)
179  call lock_mpi()
180  call mpi_get_count(status, mpi_datatype, recv_count, ierr)
181  call unlock_mpi()
182  data_receive=recv_count
183  else if (present(description_data)) then
184  call lock_mpi()
185  call mpi_irecv(description_data, num_elements, mpi_datatype, source, data_tag, mpi_comm_world, request, ierr)
186  call unlock_mpi()
187  call wait_for_mpi_request(request, status)
188  call lock_mpi()
189  call mpi_get_count(status, mpi_datatype, recv_count, ierr)
190  call unlock_mpi()
191  data_receive=recv_count
192  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ free_mpi_type()

subroutine, public mpi_communication_mod::free_mpi_type ( integer, intent(in)  the_type)

Frees an MPI type, used in clean up.

Parameters
the_typeThe MPI type to free up

Definition at line 273 of file mpicommunication.F90.

274  integer, intent(in) :: the_type
275 
276  integer :: ierr
277 
278  call mpi_type_free(the_type, ierr)
Here is the caller graph for this function:

◆ get_my_io_rank()

integer function, public mpi_communication_mod::get_my_io_rank ( integer, intent(in)  io_comm)

Retrieves my IO server rank out of the number of IO servers that are running.

Parameters
io_commThe IO server communicator
Returns
My IO server rank

Definition at line 139 of file mpicommunication.F90.

140  integer, intent(in) :: io_comm
141 
142  integer :: number, ierr
143 
144  call mpi_comm_rank(io_comm, number, ierr)
145  get_my_io_rank=number
Here is the caller graph for this function:

◆ get_number_io_servers()

integer function, public mpi_communication_mod::get_number_io_servers ( integer, intent(in)  io_comm)

Retrieves the number of IO servers that are running in total.

Parameters
io_commThe IO server communicator
Returns
The number of running IO servers

Definition at line 127 of file mpicommunication.F90.

128  integer, intent(in) :: io_comm
129 
130  integer :: number, ierr
131 
132  call mpi_comm_size(io_comm, number, ierr)
133  get_number_io_servers=number
Here is the caller graph for this function:

◆ initialise_mpi_communication()

subroutine, public mpi_communication_mod::initialise_mpi_communication ( integer, intent(in)  provided_threading)

Initialises MPI communication.

Parameters
provided_threadingThe provided threading mode

Definition at line 45 of file mpicommunication.F90.

46  integer, intent(in) :: provided_threading
47 
48  mpi_threading_mode=provided_threading
49  if (mpi_threading_mode .ne. mpi_thread_multiple .and. mpi_threading_mode .ne. mpi_thread_serialized) then
50  call log_master_log(log_error, "You must run MONC in MPI thread serialized or thread multiple mode for the IO server")
51  end if
52  manage_mpi_thread_safety=provided_threading == mpi_thread_serialized
53  call check_thread_status(forthread_mutex_init(mpi_mutex, -1))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ lock_mpi()

subroutine, public mpi_communication_mod::lock_mpi

If we are explicitly managing MPI thread safety (SERIALIZED mode) then locks MPI.

Definition at line 57 of file mpicommunication.F90.

58  if (manage_mpi_thread_safety) call check_thread_status(forthread_mutex_lock(mpi_mutex))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ pause_for_mpi_interleaving()

subroutine, public mpi_communication_mod::pause_for_mpi_interleaving

Pauses for a specific number of ms to allow for MPI interleaving, this is to avoid starvation.

Definition at line 67 of file mpicommunication.F90.

68  call usleep(int(ms_wait_between_tests, c_int32_t))
Here is the caller graph for this function:

◆ register_command_receive()

subroutine, public mpi_communication_mod::register_command_receive

Registers a request for receiving a command from any MONC process on the command channel.

Definition at line 149 of file mpicommunication.F90.

150  integer :: ierr
151 
152  call lock_mpi()
153  call mpi_irecv(command_buffer, 1, mpi_int, mpi_any_source, command_tag, &
154  mpi_comm_world, command_request_handle, ierr)
155  call unlock_mpi()
Here is the call graph for this function:
Here is the caller graph for this function:

◆ test_for_command()

logical function, public mpi_communication_mod::test_for_command ( integer, intent(out)  command,
integer, intent(out)  source 
)

Tests for a command message based upon the request already registered.

Parameters
commandThe command which is received is returned to the caller
sourceThe PID of the source MONC process is returned to the caller
Returns
Whether a message is received or not

Definition at line 218 of file mpicommunication.F90.

219  integer, intent(out) :: command, source
220 
221  integer :: ierr, status(MPI_STATUS_SIZE), complete
222 
223  call lock_mpi()
224  call mpi_test(command_request_handle, complete, status, ierr)
225  call unlock_mpi()
226 
227  if (complete .eq. 1) then
228  command = command_buffer
229  source = status(mpi_source)
230  call register_command_receive()
231  test_for_command=.true.
232  else
233  test_for_command=.false.
234  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ test_for_inter_io()

logical function, public mpi_communication_mod::test_for_inter_io ( type(io_configuration_inter_communication_description), dimension(:), intent(inout)  inter_io_communications,
integer, intent(in)  number_of_inter_io,
integer, intent(in)  io_communicator,
integer, intent(out)  command,
integer, intent(out)  source,
character, dimension(:), intent(inout), allocatable  data_buffer 
)

Tests for inter IO server communication.

Parameters
inter_io_communicationsData structures representing the possible inter IO communication sources
number_of_inter_ioNumber of inter IO communication descriptions registered
commandThe command which is received is returned to the caller
sourceThe source of the inter IO communication, which is set to the index of the inter descriptor
Returns
Whether a message is received or not

Definition at line 243 of file mpicommunication.F90.

244  integer, intent(in) :: number_of_inter_io, io_communicator
245  integer, intent(out) :: command, source
246  type(io_configuration_inter_communication_description), dimension(:), intent(inout) :: inter_io_communications
247  character, dimension(:), allocatable, intent(inout) :: data_buffer
248 
249  integer :: i, ierr, status(MPI_STATUS_SIZE), message_size
250  logical :: message_pending
251 
252  call lock_mpi()
253  do i=1, number_of_inter_io
254  call mpi_iprobe(mpi_any_source, inter_io_communications(i)%message_tag, io_communicator, message_pending, status, ierr)
255  if (message_pending) then
256  call mpi_get_count(status, mpi_byte, message_size, ierr)
257  allocate(data_buffer(message_size))
258  call mpi_recv(data_buffer, message_size, mpi_byte, mpi_any_source, inter_io_communications(i)%message_tag, &
259  io_communicator, mpi_status_ignore, ierr)
260  call unlock_mpi()
261  command=inter_io_communication
262  source=i
263  test_for_inter_io=.true.
264  return
265  end if
266  end do
267  call unlock_mpi()
268  test_for_inter_io=.false.
Here is the call graph for this function:
Here is the caller graph for this function:

◆ unlock_mpi()

subroutine, public mpi_communication_mod::unlock_mpi

If we are explicitly managing MPI thread safety (SERIALIZED mode) then unlocks MPI.

Definition at line 62 of file mpicommunication.F90.

63  if (manage_mpi_thread_safety) call check_thread_status(forthread_mutex_unlock(mpi_mutex))
Here is the call graph for this function:
Here is the caller graph for this function:

◆ wait_for_mpi_request()

subroutine, public mpi_communication_mod::wait_for_mpi_request ( integer, intent(inout)  request,
integer, dimension(mpi_status_size), intent(inout), optional  status 
)

Waits for a specific MPI request to complete, either by managing thread safety and interleaving or just a call to MPI if we are in multiple mode.

Parameters
requestThe MPI request handle

Definition at line 74 of file mpicommunication.F90.

75  integer, intent(inout) :: request
76  integer, intent(inout), optional :: status(MPI_STATUS_SIZE)
77 
78  integer :: ierr, flag
79 
80  if (manage_mpi_thread_safety) then
81  flag=0
82  do while (flag .ne. 1)
83  call lock_mpi()
84  if (present(status)) then
85  call mpi_test(request, flag, status, ierr)
86  else
87  call mpi_test(request, flag, mpi_status_ignore, ierr)
88  end if
89  call unlock_mpi()
90  if (flag .ne. 1) call pause_for_mpi_interleaving()
91  end do
92  else
93  if (present(status)) then
94  call mpi_wait(request, status, ierr)
95  else
96  call mpi_wait(request, mpi_status_ignore, ierr)
97  end if
98  end if
Here is the call graph for this function:
Here is the caller graph for this function:

◆ waitall_for_mpi_requests()

subroutine, public mpi_communication_mod::waitall_for_mpi_requests ( integer, dimension(:), intent(inout)  requests,
integer, intent(in)  count 
)

Waits for all MPI requests to complete, either by managing thread safety and interleaving or just a call to MPI if we are in multiple mode.

Parameters
requestsThe MPI request handles to wait for
countThe number of request handles to wait for

Definition at line 105 of file mpicommunication.F90.

106  integer, dimension(:), intent(inout) :: requests
107  integer, intent(in) :: count
108 
109  integer :: ierr, flag
110 
111  if (manage_mpi_thread_safety) then
112  flag=0
113  do while (flag .ne. 1)
114  call lock_mpi()
115  call mpi_testall(count, requests, flag, mpi_statuses_ignore, ierr)
116  call unlock_mpi()
117  if (flag .ne. 1) call pause_for_mpi_interleaving()
118  end do
119  else
120  call mpi_waitall(count, requests, mpi_statuses_ignore, ierr)
121  end if
Here is the call graph for this function:
Here is the caller graph for this function:

Variable Documentation

◆ command_buffer

integer mpi_communication_mod::command_buffer

Buffer used to receive the command data into when it arrives on that channel.

Definition at line 32 of file mpicommunication.F90.

32  integer :: command_buffer,& !< Buffer used to receive the command data into when it arrives on that channel
33  command_request_handle, & !< Request handle representing the asynchronous P2P command request
34  mpi_threading_mode

◆ command_request_handle

integer mpi_communication_mod::command_request_handle
private

Request handle representing the asynchronous P2P command request.

Definition at line 32 of file mpicommunication.F90.

◆ manage_mpi_thread_safety

logical mpi_communication_mod::manage_mpi_thread_safety
private

Definition at line 36 of file mpicommunication.F90.

36  logical :: manage_mpi_thread_safety

◆ mpi_mutex

integer, volatile mpi_communication_mod::mpi_mutex
private

Definition at line 35 of file mpicommunication.F90.

35  integer, volatile :: mpi_mutex

◆ mpi_threading_mode

integer mpi_communication_mod::mpi_threading_mode
private

Definition at line 32 of file mpicommunication.F90.

◆ ms_wait_between_tests

integer, parameter mpi_communication_mod::ms_wait_between_tests =100
private

Interface to the C usleep Linux call which allows us to sleep for a specific number of MS.

Definition at line 21 of file mpicommunication.F90.

21  integer, parameter :: MS_WAIT_BETWEEN_TESTS=100
logging_mod::log_error
integer, parameter, public log_error
Only log ERROR messages.
Definition: logging.F90:11
logging_mod::log_log
subroutine, public log_log(level, message, str)
Logs a message at the specified level. If the level is above the current level then the message is ig...
Definition: logging.F90:75
logging_mod::log_master_log
subroutine, public log_master_log(level, message)
Will log just from the master process.
Definition: logging.F90:47