YAP 7.1.0
lam_mpi.yap
1% Author: Nuno A. Fonseca
2% Date: 2006-06-01
3% $Id: lam_mpi.yap,v 1.1 2006-06-04 18:43:38 nunofonseca Exp $
4
5
6:- module(lam_mpi, [
7 mpi_init/0,
8 mpi_finalize/0,
20 mpi_bcast/2,
21 mpi_ibcast2/2,
22 mpi_ibcast2/3,
24 mpi_bcast2/3,
25 mpi_barrier/0,
26 mpi_msg_buffer_size/2,
28 mpi_gc/0,
29 mpi_default_buffer_size/2
30 ]).
31
32/**
33 * @defgroup lam_mpi MPI Interface
34 * @ingroup YAPLibrary
35@{
36
37This library provides a set of utilities for interfacing with LAM MPI.
38The following routines are available once included with the
39`use_module(library(lam_mpi))` command. The yap should be
40invoked using the LAM mpiexec or mpirun commands (see LAM manual for
41more details).
42
43
44*/
45
46
47/** @pred mpi_barrier
48
49
50Collective communication predicate. Performs a barrier
51synchronization among all processes. Note that a collective
52communication means that all processes call the same predicate. To be
53able to use a regular `mpi_recv` to receive the messages, one
54should use `mpi_bcast2`.
55*/
56/** @pred mpi_bcast2(+ _Root_, ? _Data_)
57
58
59
60Broadcasts the message _Data_ from the process with rank _Root_
61to all other processes.
62
63
64*/
65/** @pred mpi_comm_rank(- _Rank_)
66
67
68Unifies _Rank_ with the rank of the current process in the MPI environment.
69
70
71*/
72/** @pred mpi_comm_size(- _Size_)
73
74
75Unifies _Size_ with the number of processes in the MPI environment.
76
77
78*/
79/** @pred mpi_finalize
80
81
82Terminates the MPI execution environment. Every process must call this predicate before exiting.
83
84
85*/
86/** @pred mpi_gc
87
88
89
90Attempts to perform garbage collection with all the open handles
91associated with send and non-blocking broadcasts. For each handle it
92tests it and the message has been delivered the handle and the buffer
93are released.
94
95
96
97
98 */
99/** @pred mpi_init
100
101
102Sets up the mpi environment. This predicate should be called before any other MPI predicate.
103
104
105*/
106/** @pred mpi_irecv(? _Source_,? _Tag_,- _Handle_)
107
108
109
110Non-blocking communication predicate. The predicate returns an
111 _Handle_ for a message that will be received from processor with
112rank _Source_ and tag _Tag_. Note that the predicate succeeds
113immediately, even if no message has been received. The predicate
114`mpi_wait_recv` should be used to obtain the data associated to
115the handle.
116
117
118*/
119/** @pred mpi_isend(+ _Data_,+ _Dest_,+ _Tag_,- _Handle_)
120
121
122
123Non blocking communication predicate. The message in _Data_, with
124tag _Tag_, is sent whenever possible to the processor with rank
125 _Dest_. An _Handle_ to the message is returned to be used to
126check for the status of the message, using the `mpi_wait` or
127`mpi_test` predicates. Until `mpi_wait` is called, the
128memory allocated for the buffer containing the message is not
129released.
130
131
132*/
133/** @pred mpi_msg_size( _Msg_, - _MsgSize_)
134
135
136Unify _MsgSize_ with the number of bytes YAP would need to send the
137message _Msg_.
138
139
140*/
141/** @pred mpi_recv(? _Source_,? _Tag_,- _Data_)
142
143
144
145Blocking communication predicate. The predicate blocks until a message
146is received from processor with rank _Source_ and tag _Tag_.
147The message is placed in _Data_.
148
149
150*/
151/** @pred mpi_send(+ _Data_,+ _Dest_,+ _Tag_)
152
153
154
155Blocking communication predicate. The message in _Data_, with tag
156 _Tag_, is sent immediately to the processor with rank _Dest_.
157The predicate succeeds after the message being sent.
158
159
160*/
161/** @pred mpi_test(? _Handle_,- _Status_)
162
163
164
165Provides information regarding the handle _Handle_, ie., if a
166communication operation has been completed. If the operation
167associate with _Hanlde_ has been completed the predicate succeeds
168with the completion status in _Status_, otherwise it fails.
169
170
171*/
172/** @pred mpi_test_recv(? _Handle_,- _Status_,- _Data_)
173
174
175
176Provides information regarding a handle. If the message associated
177with handle _Hanlde_ is buffered then the predicate succeeds
178unifying _Status_ with the status of the message and _Data_
179with the message itself. Otherwise, the predicate fails.
180
181
182*/
183/** @pred mpi_version(- _Major_,- _Minor_)
184
185
186Unifies _Major_ and _Minor_ with, respectively, the major and minor version of the MPI.
187
188
189*/
190/** @pred mpi_wait(? _Handle_,- _Status_)
191
192
193
194Completes a non-blocking operation. If the operation was a
195`mpi_send`, the predicate blocks until the message is buffered
196or sent by the runtime system. At this point the send buffer is
197released. If the operation was a `mpi_recv`, it waits until the
198message is copied to the receive buffer. _Status_ is unified with
199the status of the message.
200
201
202*/
203/** @pred mpi_wait_recv(? _Handle_,- _Status_,- _Data_)
204
205
206
207Completes a non-blocking receive operation. The predicate blocks until
208a message associated with handle _Hanlde_ is buffered. The
209predicate succeeds unifying _Status_ with the status of the
210message and _Data_ with the message itself.
211
212
213*/
214
215:- load_foreign_files([libYAPmpi], [], init_mpi).
216
217mpi_msg_size(Term, Size) :-
218 mpi_msg_size:export_term(Term, Buf, Size),
219 export_term:kill_exported_term(Buf).
220/** @} */
221
222
load_foreign_files( Files, Libs, InitRoutine)
mpi_bcast2(+ Root, ? Data)
mpi_comm_rank(- Rank)
mpi_comm_size(- Size)
mpi_irecv(? Source,? Tag,- Handle)
mpi_isend(+ Data,+ Dest,+ Tag,- Handle)
mpi_msg_size( Msg, - MsgSize)
mpi_recv(? Source,? Tag,- Data)
mpi_send(+ Data,+ Dest,+ Tag)
mpi_test(? Handle,- Status)
mpi_test_recv(? Handle,- Status,- Data)
mpi_version(- Major,- Minor)
mpi_wait(? Handle,- Status)
mpi_wait_recv(? Handle,- Status,- Data)