1/*****************************************************************************
    2 * This file is part of the Prolog Development Tool (PDT)
    3 * 
    4 * Author: Lukas Degener (among others)
    5 * WWW: http://sewiki.iai.uni-bonn.de/research/pdt/start
    6 * Mail: pdt@lists.iai.uni-bonn.de
    7 * Copyright (C): 2004-2012, CS Dept. III, University of Bonn
    8 * 
    9 * All rights reserved. This program is  made available under the terms
   10 * of the Eclipse Public License v1.0 which accompanies this distribution,
   11 * and is available at http://www.eclipse.org/legal/epl-v10.html
   12 * 
   13 ****************************************************************************/
   14
   15/*
   16 * to activate debugging for this module, uncomment:
   17 */
   18% :- debug(process_observe).
   19
   20:- module(process_observe,[
   21	process_observe/3,
   22	process_observe/2,	
   23	process_unobserve/2,
   24	process_notify/2,
   25	process_dispatch/3
   26]).   27
   28:- use_module(library(debug)).   29
   30:-dynamic process_observe_hook/3,process_unobserve_hook/3.   31:-multifile process_observe_hook/3,process_unobserve_hook/3.   32
   33% process_observe_hook(Thread,Subject,Key),
   34% A hook predicate that will be called each time an observer registers to 
   35% a subject, if it is not already registered with this subject.
   36% Clients that provide observable subjects can add clauses to these predicates
   37% if they need to take additional actions on registration of an observer
   38% to a subject. If the call succeeds, it is assumes that these additional actions have 
   39% been taken.
   40% 
   41process_observe_hook(_,_,_):-
   42	fail.	     	
   43
   44% process_unobserve_hook(Thread,Subject,Key),
   45% A hook predicate that will be called each time an observer unregisters to 
   46% a subject. see process_observe_hook/3
   47% 
   48process_unobserve_hook(_,_,_):-
   49	fail.	     	
   50
   51call_observe_hook(Thread,Subject,Key):-
   52	catch(process_observe_hook(Thread,Subject,Key),E,print_message(error,E)),
   53	!.  
   54call_observe_hook(_,_,_).
   55call_unobserve_hook(Thread,Subject,Key):-
   56	catch(process_unobserve_hook(Thread,Subject,Key),E,print_message(error,E)),
   57	!.  		
   58call_unobserve_hook(_,_,_).	
   59
   60
   61/*
   62 * backwards compatibility. 
   63 */
   64process_observe(Thread,Subject):-
   65   term_to_atom(Subject,Key),
   66   process_observe(Thread,Subject,Key). 
 process_observe(+Thread, +Subject)
Add an observer to a subject.
Arguments:
Thread- the observer, i.e. a thread that is running dispatch/3
Subject- the subject to observe. This term is unified with the subject given as second argument to notify/2.
Key- should be an atom. During notification, if the Subject terms was successfully unified, the key is also passed to the observer. The idea of this is to help observers calling from Java, or otherwise lacking the concept of unification, to recognize the Subject they subscribed for.
   80process_observe(Thread,Subject,Key) :-
   81  recorded(process_observer,observation(Thread,OtherSubject,Key), _),
   82  OtherSubject =@= Subject,
   83  !.
   84
   85process_observe(Thread,Subject,Key) :-
   86%  sync:init_idb(Subject),
   87  call_observe_hook(Thread,Subject,Key),
   88  recordz(process_observer,observation(Thread,Subject,Key), _).
 process_unobserve(+Thread, +Subject)
Remove an observer from a subject.
Arguments:
Thread- the observer thread to remove.
Subject- the subject from which to remove the observer.
   99process_unobserve(Thread,Subject) :-
  100  recorded(process_observer,observation(Thread,OtherSubject,Key),Ref),
  101  OtherSubject =@= Subject,
  102  erase(Ref),
  103  %sync:unregister_observer(Subject). 
  104  call_unobserve_hook(Thread,Subject,Key).
 process_notify(+Subject, +Event)
Notify all active observers. If observer's thread is stopped it will be removed.
  111process_notify(Subject,Event) :-
  112   debug(process_observe,'~w~n',[process_notify(Subject,Event)]),
  113   forall(
  114    	( 
  115    	  recorded(process_observer,observation(Thread,Subject,_),Ref)
  116    	),
  117    	(	current_thread(Thread,running)
  118    	->	(    	      
  119    	      thread_send_message(Thread,notify(Subject,Event)),
  120   	      debug(process_observe,'~w~n',[thread_send_message(Thread,notify(Subject,Event))])
  121    	   
  122    	);	erase(Ref)
  123    	)
  124    ).   
 process_dispatch(-Subject, -Key, -Event)
Recieve events. This predicate is intended to be called by observer threads. It produces solutions for every recieved event, i.e. every time process_notify/2 is called on a subject the observer thread is subscribed for. If it recieves an event for the subject '$stop' it will cut and fail.
  134 process_dispatch(Subject,Key,Event):-
  135     	thread_self(Me),
  136     	repeat,
  137	     	thread_get_message(notify(Subject,Event)),
  138	     	(	Subject='$abort'
  139	     	->	!
  140	     	;	recorded(process_observer,observation(Me,Subject,Key), _)
  141	     	)