1:- module(canny_situations, [situation_apply/2, situation_property/2]).    2
    3:- meta_predicate
    4    situation_apply(:, ?),              % ?Situation, ?Apply
    5    situation_property(:, ?).           % ?Situation, ?Property
    6
    7:- multifile
    8    canny:apply_to_situation/2,
    9    canny:property_of_situation/2.   10
   11:- use_module(library(random/temporary)).   12
   13:- dynamic situation_module/2.
 situation_apply(?Situation:any, ?Apply) is nondet
Mutates Situation. Apply term to Situation, where Apply is one of the following. Note that the Apply term may be nonground. It can contain variables if the situation mutation generates new information.
module(?Module)
Sets up Situation using Module. Establishes the dynamic predicate options for the temporary situation module used for persisting situation Now-At and Was-When tuples.

An important side effect occurs for ground Situation terms. The implementation creates the situation's temporary module and applies default options to its new dynamic predicates. The module(Module) term unifies with the newly-created or existing situation module.

The predicate's determinism collapses to semi-determinism for ground situations. Otherwise with variable Situation components, the predicate unifies with all matching situations, unifying with module(Module) non-deterministically.

now(+Now:any)
now(+Now:any, +At:number)
Makes some Situation become Now for time index At, at the next fixation. Effectively schedules a pending update one or more times; the next situation fix/0 fixes the pending situation changes at some future point. The now/1 form applies Now to Situation at the current Unix epoch time.

Uses apply_to_situation/2 when Situation is ground, but uses property_of_situation/2 otherwise. Asserts therefore for multiple situations if Situation comprises variables. You cannot therefore have non-ground situations.

fix
fix(+Now:any)
Fixating situations does three important things. First, it adds new Previous-When pairs to the situation history. They become was/2 dynamic facts (clauses without rules). Second, it adds, replaces or removes the most current Current-When pair. This allows detection of non-events, e.g. when something disappears. Some types of situation might require such event edges. Finally, fixating broadcasts situation-change messages.

The rule for fixing the Current-When pair goes like this: Is there a new now/2, at least one? The latest becomes the new current. Any others become Previous-When. If there is no now/2, then the current disappears. Messages broadcast accordingly. If there is more than one now/2, only the latest becomes current. Hence currently-previously only transitions once in-between fixations.

Term fix/1 is a shortcut for now(Now, At) and fix where At becomes the current Unix epoch time. Fixes but does not retract history terms.

retract(+When:number)
retract(?When:number, +Delay:number)
Retracts all was/2 clauses for all matching Situation terms. Term retract(_, Delay) retracts all was/2 history terms using the last term's latest time stamp. In this way, you can retract situations without knowing their absolute time. For example, you can retract everything older than 60 seconds from the last known history term when you retract(_, 60).

The second argument Apply can be a list of terms to apply, including nested lists of terms. All terms apply in order first to last, and depth first.

Arguments:
Now- is the state of a Situation at some point in time. The Now term must be non-variable but not necessarily ground. Dictionaries with unbound tags can exist within the situation calculus.
   94situation_apply(Situation, Apply) :- applies(Apply, Situation).
   95
   96applies(Applies, Situation) :-
   97    is_list(Applies),
   98    !,
   99    member(Apply, Applies),
  100    applies(Apply, Situation).
  101applies(Apply, Situation) :- canny:apply_to_situation(Apply, Situation).
  102
  103canny:apply_to_situation(module(Module), Situation) :-
  104    with_mutex(canny_situations, temporary_module(Situation, Module)).
  105
  106temporary_module(Situation, Module) :- situation_module(Situation, Module), !.
  107temporary_module(Situation, Module) :-
  108    ground(Situation),
  109    once(random_temporary_module(Module)),
  110    asserta(situation_module(Situation, Module)),
  111    dynamic([   Module:now/2,
  112                Module:was/2,
  113                Module:currently/2,
  114                Module:previously/2
  115            ], []).
  116
  117canny:apply_to_situation(now(Now, At), Situation) :-
  118    nonvar(Now),
  119    number(At),
  120    now(Situation, Now, At).
  121canny:apply_to_situation(now(Now), Situation) :-
  122    get_time(At),
  123    canny:apply_to_situation(now(Now, At), Situation).
  124
  125now(Situation, Now, At) :-
  126    ground(Situation),
  127    !,
  128    temporary_module(Situation, Module),
  129    assertz(Module:now(Now, At)).
  130now(Situation, Now, At) :-
  131    forall(situation_module(Situation, Module), assertz(Module:now(Now, At))).
  132
  133canny:apply_to_situation(fix, Situation) :-
  134    situation_module(Situation, Module),
  135    fix(Situation, Module).
  136
  137fix(Situation, Module) :-
  138    findall(now(Now, At), retract(Module:now(Now, At)), Fixes0),
  139    sort(2, @=<, Fixes0, Fixes),
  140    forall(member(now(Was, When), Fixes), asserta(Module:was(Was, When))),
  141    ignore(retractall(Module:previously(_, _))),
  142    fix(Fixes, Situation, Module),
  143    broadcast(situation(Situation, fix)).
  144
  145fix([], Situation, Module) :-
  146    once(retract(Module:currently(Previous, When))),
  147    !,
  148    asserta(Module:previously(Previous, When)),
  149    broadcast(situation(Situation, was(Previous, When))).
  150fix([], _, _) :- !.
  151fix(Fixes, Situation, Module) :-
  152    last(Fixes, now(Now, At)),
  153    fix(Situation, Module, Now, At).
  154
  155fix(_, Module, Now, _) :- once(Module:currently(Now, _)), !.
  156fix(Situation, Module, Now, At) :-
  157    once(retract(Module:currently(Previous, When))),
  158    !,
  159    asserta(Module:previously(Previous, When)),
  160    asserta(Module:currently(Now, At)),
  161    broadcast(situation(Situation, was(Previous, When), now(Now, At))).
  162fix(Situation, Module, Now, At) :-
  163    asserta(Module:currently(Now, At)),
  164    broadcast(situation(Situation, now(Now, At))).
  165
  166canny:apply_to_situation(retract(When), Situation) :-
  167    situation_module(Situation, Module),
  168    retract(Situation, Module, When).
  169
  170retract(Situation, Module, When0) :-
  171    forall((   Module:was(Was, When),
  172               When < When0
  173           ), once(retract(Module:was(Was, When)))),
  174    broadcast(situation(Situation, retract(When0))).
  175
  176canny:apply_to_situation(retract(When, Delay), Situation) :-
  177    number(Delay),
  178    situation_module(Situation, Module),
  179    retract(Situation, Module, When, Delay).
  180
  181retract(Situation, Module, When, Delay) :-
  182    var(When),
  183    !,
  184    once(Module:was(_, When)),
  185    retract(Situation, Module, When, Delay).
  186retract(Situation, Module, When, Delay) :-
  187    When0 is When - Delay,
  188    retract(Situation, Module, When0).
  189
  190canny:apply_to_situation(fix(Now, At), Situation) :-
  191    canny:apply_to_situation(now(Now, At), Situation),
  192    canny:apply_to_situation(fix, Situation).
  193canny:apply_to_situation(fix(Now), Situation) :-
  194    canny:apply_to_situation(now(Now), Situation),
  195    canny:apply_to_situation(fix, Situation).
  196canny:apply_to_situation(fixate(Now, Delay), Situation) :-
  197    get_time(At),
  198    canny:apply_to_situation(fix(Now, At), Situation),
  199    canny:apply_to_situation(retract(At, Delay), Situation).
  200
  201canny:apply_to_situation(listing, Situation) :-
  202    situation_module(Situation, Module),
  203    listing(Module:_).
 situation_property(?Situation:any, ?Property) is nondet
Property of Situation.
module(?Module)
Marries situation terms with universally-unique modules, one for one. All dynamic situations link a situation term with a module. This design addresses performance. Retracts take a long time, relatively, especially for dynamic predicates with very many clauses; upwards of 10,000 clauses for example. Note, you can never delete the situation-module association, but you can retract all the dynamic clauses belonging to a situation.
defined
Situation is defined whenever a unique situation module already exists for the given Situation. Amounts to the same as asking for module(_) property.
currently(?Current:any)
currently(?Current:any, ?When:number)
currently(Current:any,for(Seconds:number))
Unifies with Current for Situation and When it happened. Unifies with the one and only Current state for all the matching Situation terms. Unifies non-deterministically for all Situation solutions, but semi-deterministically for Current state. Thus allows for multiple matching situations but only one Current solution.

You can replace the When term with for(Seconds) in order to measure elapsed interval since fixing Situation. Same applies to previously/2 except that the current situation time stamp serves as the baseline time, else defaults to the current time.

previously(?Previous:any)
previously(?Previous:any, ?When:number)
previously(Previous:any,for(Seconds:number))
Finds Previous state of Situation, non-deterministically resolving zero or more matching Situation terms. Fails if no previous Situation condition.
history(?History:list(compound))
Unifies History with all current and previous situation conditions, including their time stamps. History is a sequence of compounds of the form was(Was, When) where Situation is effectively a primitive condition coordinate, Was is a sensing outcome and When marks the moment that the outcome transpired.
  257situation_property(Situation, Property) :-
  258    canny:property_of_situation(Property, Situation).
  259
  260canny:property_of_situation(module(Module), Situation) :-
  261    situation_module(Situation, Module).
  262canny:property_of_situation(defined, Situation) :-
  263    situation_module(Situation, _).
  264canny:property_of_situation(currently(Current, When), Situation) :-
  265    situation_module(Situation, Module),
  266    once(Module:currently(Current, When0)),
  267    currently_for(When, When0).
  268canny:property_of_situation(currently(Current), Situation) :-
  269    canny:property_of_situation(currently(Current, _), Situation).
  270canny:property_of_situation(previously(Previous, When), Situation) :-
  271    situation_module(Situation, Module),
  272    once(Module:previously(Previous, When0)),
  273    previously_for(When, When0, Situation).
  274canny:property_of_situation(previously(Previous), Situation) :-
  275    canny:property_of_situation(previously(Previous, _), Situation).
  276canny:property_of_situation(history(History), Situation) :-
  277    situation_module(Situation, Module),
  278    findall(was(Was, When), Module:was(Was, When), History).
 currently_for(?When, +When0) is det
The predicate has three outcomes. (1) Unifies When with When0 if unbound. (2) If When unifies with for(Seconds) then Seconds unifies with the difference between the last When stamp and the current time stamp. This assumes that the situation time carries the same time scale as Epoch time. This is not always necessarily the case, however. (3) By default, the outgoing When unifies with the incoming When0.
  290currently_for(When, When0) :- var(When), !, When = When0.
  291currently_for(for(Seconds), When) :- !, get_time(At), Seconds is At - When.
  292currently_for(When, When).
 previously_for(?When, +When0, +Situation) is det
Previously for(Seconds) compares the previous When with the current When, assuming Situation answers to currently(Current, When). Situations may have a previous without a current if fixed without a Now term.
  301previously_for(When, When0, _Situation) :- var(When), !, When = When0.
  302previously_for(for(Seconds), When, Situation) :-
  303    !,
  304    currently_at(At, Situation),
  305    Seconds is At - When.
  306previously_for(When, When, _Situation).
  307
  308currently_at(At, Situation) :-
  309    canny:property_of_situation(currently(_, At), Situation),
  310    !.
  311currently_at(At, _Situation) :- get_time(At)