[ Reference Manual | Alphabetic Index ]

library(notify_ports)

One-to-many and many-to-many notification ports   [more]

Predicates

close_sender(+SendPort)
Close a send port
close_sender(+Pos, +Struct)
Close a send port on a structure field
foreachnotification(+BaseName, -Message, +Params, +ReceivePort, -Status, +Goals)
A control construct to iterate over received notifications
foreachnotification(+BaseName, -Message, +Params, +ReceivePos, +ReceiveStruct, -Status, +Goals)
A control construct to iterate over received notifications
merge_senders(+DyingSender, +SurvivingSender)
Merge DyingSender into SurvivingSender
open_receiver(+SendPort, -ReceivePort)
Create a receiver for a given notification sender
open_receiver(+SendPos, +SendStruct, +ReceivePos, +ReceiveStruct)
Create a receiver for a given notification sender
open_receiver_init(+SendPort, +InitialMessages, -InitialMessagesTail, -ReceivePort)
Create a receiver for a given notification sender
open_receiver_init(+SendPos, +SendStruct, +InitialMessages, -InitialMessagesTail, +ReceivePos, +ReceiveStruct)
Create a receiver for a given notification sender
open_sender(-SendPort)
Create a send port
open_sender(+Pos, +Struct)
Initialise a structure field as a send port
open_tagged_receiver(+Tag, +SendPort, ?ReceivePort)
Create a receiver for one or more tagging senders
open_tagging_sender(-SendPort)
Create a many-to-many send port
receive_notifications(+ReceivePort, -Messages, -Status)
Receive a list of currently available notification messages
receive_notifications(+ReceivePos, +ReceiveStruct, -Messages, -Status)
Receive a list of currently available notification messages
send_notification(+SendPort, +Message)
Send a notification message
send_notification(+Pos, +Struct, +Message)
Send a notification message

Description

This library implements a nonlogical feature, called notification ports. They are a form of messaging, i.e. there is are send ports and attached receive ports, and messages in the form of general terms can be passed through these ports. Both send and receive ports have unique handles, which is the nonlogical bit.

There are two variants of this feature, one-to-many and many-to-many ports.

One-To-Many

In the one-to-many variant, messages sent from a single send port can be received independently by several receivers. In this setting, the message stream is essentially an infinite list, with the sender extending the list at the tail and the receivers each individually progressing through the list.

Straightforward interface:

	open_sender(-Sender)
	close_sender(+Sender)
	send_notification(+Sender, +Message)
	open_receiver(+Sender, -Receiver)
	open_receiver_init(+Sender, +InitMsgs, -InitMsgsTail, -Receiver)
	receive_notifications(+Receiver, -Messages, -Status)
	foreachnotification(+BaseName, -Message, +Params, +Receiver, -Status, +Goals)
    
There is also a slightly more memory efficient API where sender and receiver can be fields of larger structures rather than separate substructures. These larger structures must always be created by the caller (in the case of the sender this is often an attribute structure, in the case of the receiver it is sometimes advantageous to package a suspension together with the receiver in order to kill it at the end of all messages):
	open_sender(+SendPos, +SendStruct)
	close_sender(+SendPos, +SendStruct)
	send_notification(+SendPos, +SendStruct, +Message)
	open_receiver(+SendPos, +SendStruct, +ReceivePos, +ReceiveStruct)
	open_receiver_init(+SendPos, +SendStruct, +InitMsgs, -InitMsgsTail,
				+ReceivePos, +ReceiveStruct)
	receive_notifications(+ReceivePos, +ReceiveStruct, -Messages, -Status)
	foreachnotification(+BaseName, -Message, +Params, +ReceivePos, +ReceiveStruct, -Status, +Goals)
    

Many-To-Many

In the many-to-many variant, several send ports can be connected to several receive ports in an arbitray manner. To enable a receiver to distinguish messages from multiple senders, the messages get tagged with a sender- and receiver-specific id as they are received.

The corresponding predicates are the following. Note that sender and receiver are opened with different predicates, but the send and receive predicates are the same as for one-to-many ports:
	open_tagging_sender(-Sender)
	open_tagged_receiver(+Tag, +Sender, -Receiver)

	send_notification(+Sender, +Message)
	receive_notifications(+Receiver, -Messages, -Status)
	foreachnotification(+BaseName, -Message, +Params, +Receiver, -Status, +Goals)
    
Note that closing of tagging senders is currently not implemented.

Examples

    % One-to-many

    % This example shows a typical use of notification ports.
    % A notification port is used in addition to a waking list
    % in order to transfer precise information about the reason for waking.

    % We define a variable attribute (myattr) consisting of a send port
    % and a waking list. 


    :- lib(notify_ports).

    :- meta_attribute(myattr, []).
    :- local struct(myattr(port,susplist)).
    :- local struct(myrec(port,susp)).


    test :-
	    init_var(X),
	    log_all_messages(X),
	    touch_var(X, hello),
	    touch_var(X, out),
	    touch_var(X, there),
	    fini_var(X).


    % initialise and attach our attribute to the given variable
    init_var(X) :-
	    Attr = myattr{},
	    open_sender(port of myattr, Attr),
	    init_suspension_list(susplist of myattr, Attr),
	    add_attribute(X, Attr, myattr).


    % simulate an action on the variable: send a message and wake
    touch_var(_X{myattr:Attr}, Message) ?-
	    send_notification(port of myattr, Attr, Message),
	    schedule_suspensions(susplist of myattr, Attr),
	    wake.

    % finalise the attribute, e.g. before the variable gets instantiated
    fini_var(_X{myattr:Attr}) ?-
            close_sender(port of myattr, Attr),
	    schedule_suspensions(susplist of myattr, Attr),
	    wake.

    % a sample demon that will report every time the variable is touched
    log_all_messages(X{myattr:Attr}) ?-
	    Receiver = myrec{susp:Susp},
	    open_receiver(port of myattr, Attr, port of myrec, Receiver),
	    suspend(log_demon(Receiver), 2, X->myattr:(susplist of myattr), Susp).

    :- demon log_demon/1.
    log_demon(Receiver) :-
	    foreachnotification(log, Message, [], port of myrec, Receiver, Status, (
		writeln(received(Message))
	    )),
	    ( Status = closed ->
		arg(susp of myrec, Receiver, Susp),
		kill_suspension(Susp),
		writeln(closed)
	    ;
		true
	    ).
    

    ( For a many-to-many example, see open_tagged_receiver/3 )
    

About


Generated from notify_ports.eci on 2022-09-03 14:26