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 $
This library provides a set of utilities for interfacing with LAM MPI. The following routines are available once included with the use_module(library(lam_mpi)) command. The yap should be invoked using the LAM mpiexec or mpirun commands (see LAM manual for more details).

*/

Collective communication predicate. Performs a barrier synchronization among all processes. Note that a collective communication means that all processes call the same predicate. To be able to use a regular mpi_recv to receive the messages, one should use mpi_bcast2.

*/

Broadcasts the message Data from the process with rank Root to all other processes.

*/

Unifies Rank with the rank of the current process in the MPI environment.

*/

Unifies Size with the number of processes in the MPI environment.

*/

Terminates the MPI execution environment. Every process must call this predicate before exiting.

*/

Attempts to perform garbage collection with all the open handles associated with send and non-blocking broadcasts. For each handle it tests it and the message has been delivered the handle and the buffer are released.

/

Sets up the mpi environment. This predicate should be called before any other MPI predicate.

*/

Non-blocking communication predicate. The predicate returns an Handle for a message that will be received from processor with rank Source and tag Tag. Note that the predicate succeeds immediately, even if no message has been received. The predicate mpi_wait_recv should be used to obtain the data associated to the handle.

*/

Non blocking communication predicate. The message in Data, with tag Tag, is sent whenever possible to the processor with rank Dest. An Handle to the message is returned to be used to check for the status of the message, using the mpi_wait or mpi_test predicates. Until mpi_wait is called, the memory allocated for the buffer containing the message is not released.

*/

Unify MsgSize with the number of bytes YAP would need to send the message Msg.

*/

Blocking communication predicate. The predicate blocks until a message is received from processor with rank Source and tag Tag. The message is placed in Data.

*/

Blocking communication predicate. The message in Data, with tag Tag, is sent immediately to the processor with rank Dest. The predicate succeeds after the message being sent.

*/

Provides information regarding the handle Handle, ie., if a communication operation has been completed. If the operation associate with Hanlde has been completed the predicate succeeds with the completion status in Status, otherwise it fails.

*/

Provides information regarding a handle. If the message associated with handle Hanlde is buffered then the predicate succeeds unifying Status with the status of the message and Data with the message itself. Otherwise, the predicate fails.

*/

Unifies Major and Minor with, respectively, the major and minor version of the MPI.

*/

Completes a non-blocking operation. If the operation was a mpi_send, the predicate blocks until the message is buffered or sent by the runtime system. At this point the send buffer is released. If the operation was a mpi_recv, it waits until the message is copied to the receive buffer. Status is unified with the status of the message.

*/

Completes a non-blocking receive operation. The predicate blocks until a message associated with handle Hanlde is buffered. The predicate succeeds unifying Status with the status of the message and Data with the message itself.

*/

  189:- module(lam_mpi, [
  190                  mpi_init/0,
  191                  mpi_finalize/0,
  192                  mpi_comm_size/1,
  193                  mpi_comm_rank/1,
  194                  mpi_version/2,
  195		  mpi_send/3,
  196		  mpi_isend/4,
  197		  mpi_recv/3,
  198		  mpi_irecv/3,
  199		  mpi_wait/2,
  200		  mpi_wait_recv/3,
  201		  mpi_test/2,
  202		  mpi_test_recv/3,
  203		  mpi_bcast/2,
  204		  mpi_ibcast2/2,
  205		  mpi_ibcast3/3,
  206		  mpi_bcast2/2,
  207		  mpi_bcast3/3,
  208		  mpi_barrier/0,
  209%		  mpi_msg_buffer_size/2,
  210		  mpi_msg_size/2,
  211		  mpi_gc/0,
  212		  mpi_default_buffer_size/2
  213          ]).  214
  215:- use_foreign_library(foreign(pl_mpi),init_mpi).  216
  217
  218mpi_msg_size(Term, Size) :-
  219	terms:export_term(Term, Buf, Size),
  220	terms:kill_exported_term(Buf)