SURFEX v8.1
General documentation of Surfex
mpl_data_module.F90
Go to the documentation of this file.
2 
3 ! Author.
4 ! -------
5 ! D.Dent, M.Hamrud ECMWF
6 
7 ! Modifications.
8 ! --------------
9 ! Original: 2000-09-01
10 
11 ! ------------------------------------------------------------------
12 
13 ! variables controlling the execution of MPL
14 
15 ! MPL_METHOD : buffering type
16 ! MPL_MBX_SIZE : size of application mailbox, (bytes)
17 ! used when MPL_METHOD=JP_BLOCKING_BUFFERED
18 ! MPL_COMM : default communicator in use
19 ! MPL_COMM_OML : communicators for messages between corresponding OML-threads
20 ! MPL_UNIT : Fortran I/O unit for messages (default=6)
21 ! MPL_ERRUNIT : Fortran I/O unit for error messages (default=0)
22 ! MPL_OUTPUT : controls contents of Output (see mpl_init_mod.F90 for values/default)
23 ! MPL_RANK : rank of the process within MPL_COMM_OML(1)
24 ! MPL_NUMPROC : number of processes in MPL_COMM_OML(1)
25 ! MPL_IDS : array of processor numbers
26 ! LUSEHLMPI : always use high level MPI calls (collective comm.)
27 ! LINITMPI_VIA_MPL : true if MPI has been initialized from within MPL_INIT()
28 ! LTHSAFEMPI : Thread safe MPI, if .TRUE. (default)
29 
30 USE parkind1 ,ONLY : jpim ,jprb
32 
33 IMPLICIT NONE
34 
35 SAVE
36 
37 PUBLIC
38 
39 INTEGER(KIND=JPIM) :: mpl_method, mpl_mbx_size, mpl_unit=6, mpl_output=1
40 INTEGER(KIND=JPIM) :: mpl_rank=0,mpl_numproc = -1,mpl_errunit=0
41 INTEGER(KIND=JPIM),ALLOCATABLE :: mpl_ids(:)
42 INTEGER(KIND=JPIM) :: mpl_comm
43 INTEGER(KIND=JPIM),ALLOCATABLE :: mpl_comm_oml(:)
44 INTEGER(KIND=JPIM),ALLOCATABLE :: mpl_opponent(:)
45 INTEGER(KIND=JPIM) :: mpl_ncpu_per_node=1
46 INTEGER(KIND=JPIM) :: mpl_max_task_per_node
47 INTEGER(KIND=JPIM),ALLOCATABLE :: mpl_task_per_node(:)
48 INTEGER(KIND=JPIM) :: mpl_nnodes
49 LOGICAL :: lfullnodes
50 INTEGER(KIND=JPIM) :: mpl_mynode=0
51 INTEGER(KIND=JPIM),ALLOCATABLE :: mpl_node(:)
52 INTEGER(KIND=JPIM),ALLOCATABLE :: mpl_node_tasks(:,:)
53 !INTEGER_M,ALLOCATABLE :: MPL_ATTACHED_BUFFER(:)
54 ! needs to ge a TARGET for coexistence with MPE
55 INTEGER(KIND=JPIM),ALLOCATABLE,TARGET :: mpl_attached_buffer(:)
56 LOGICAL :: lusehlmpi
57 LOGICAL :: linitmpi_via_mpl = .false.
58 LOGICAL :: lthsafempi = .true.
59 INTEGER(KIND=JPIM),PARAMETER :: jp_attached_buffer_bytes = jpim
60 INTEGER(KIND=JPIM),PARAMETER :: jp_blocking_standard = 1
61 INTEGER(KIND=JPIM),PARAMETER :: jp_blocking_buffered = 2
62 INTEGER(KIND=JPIM),PARAMETER :: jp_blocking_synchronous = 3
63 INTEGER(KIND=JPIM),PARAMETER :: jp_blocking_ready = 4
64 INTEGER(KIND=JPIM),PARAMETER :: jp_non_blocking_standard = 5
65 INTEGER(KIND=JPIM),PARAMETER :: jp_non_blocking_buffered = 6
66 INTEGER(KIND=JPIM),PARAMETER :: jp_non_blocking_synchronous = 7
67 INTEGER(KIND=JPIM),PARAMETER :: jp_non_blocking_ready = 8
68 LOGICAL :: lmplusercomm = .false.
69 INTEGER(KIND=JPIM) :: mplusercomm = -1
70 INTEGER(KIND=JPIM) :: mpl_send_count, mpl_send_bytes
71 INTEGER(KIND=JPIM) :: mpl_recv_count, mpl_recv_bytes
72 
73 END MODULE mpl_data_module
integer(kind=jpim) mplusercomm
integer(kind=jpim), parameter jp_blocking_buffered
integer, parameter jpim
Definition: parkind1.F90:13
integer(kind=jpim) mpl_mynode
integer(kind=jpim), parameter jp_non_blocking_synchronous
integer(kind=jpim) mpl_numproc
integer(kind=jpim), dimension(:,:), allocatable mpl_node_tasks
integer(kind=jpim), dimension(:), allocatable mpl_node
integer(kind=jpim), dimension(:), allocatable mpl_task_per_node
integer(kind=jpim) mpl_send_count
integer(kind=jpim), parameter jp_non_blocking_ready
integer(kind=jpim), parameter jp_non_blocking_standard
integer(kind=jpim) mpl_nnodes
integer(kind=jpim), dimension(:), allocatable mpl_comm_oml
integer(kind=jpim), parameter jp_blocking_standard
integer(kind=jpim) mpl_max_task_per_node
integer(kind=jpim) mpl_ncpu_per_node
integer(kind=jpim), parameter jp_attached_buffer_bytes
integer(kind=jpim), parameter jp_non_blocking_buffered
integer, parameter jprb
Definition: parkind1.F90:32
integer(kind=jpim) mpl_errunit
integer(kind=jpim) mpl_comm
integer(kind=jpim), parameter jp_blocking_ready
integer(kind=jpim) function, public oml_my_thread()
Definition: oml_mod.F90:249
integer(kind=jpim), dimension(:), allocatable mpl_opponent
integer(kind=jpim), parameter jp_blocking_synchronous
integer(kind=jpim) mpl_rank
integer(kind=jpim) mpl_mbx_size
integer(kind=jpim) mpl_method
integer(kind=jpim) mpl_recv_bytes
integer(kind=jpim) function, public oml_max_threads()
Definition: oml_mod.F90:256
integer(kind=jpim) mpl_recv_count
integer(kind=jpim), dimension(:), allocatable, target mpl_attached_buffer
integer(kind=jpim), dimension(:), allocatable mpl_ids
integer(kind=jpim) mpl_unit
integer(kind=jpim) mpl_send_bytes
integer(kind=jpim) mpl_output