1% init_why(after('/opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/marty_white/planner/ec_reader.pl')).
    2% init_why(after('/opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/marty_white/planner/ec_reader.pl')).
    3% init_why(program).
    4% ec_to_pl(do_ec_load, current_output, 'ectest/TestBoxRoom.e').
    5% ectest/TestBoxRoom.e:1
    6% ec_in_to_pl(do_ec_load, current_output, <stream>(0x55638dfa3da0)).
    7% ec_io(do_ec_load, <stream>(0x55638dfa3da0)).
    8% ectest/TestBoxRoom.e:1
    9:- include('../ec_test_incl').   10
   11
   12do_test_gen(What) :- ec_current_domain(fluent(P)),functor(P,F,A),functor(What,F,A).
   13
   14local_demo(L,R):-  dbginfo('L'=L),abdemo_special(depth(0,10),L,R),!.
   15local_demo(L,R):-  dm('FAILED:',(L:-R)),trace,!,abdemo_special(depth(0,10),L,R).
   16
   17
   18dm(TF,P):- format('~N~n~w ~p.~n',[TF,P]).
   19
   20/*
   21
   22These tests Pass
   23
   24do_test(test_np_box_1) :-  local_demo([holds_at(directlyIn(lisa,livingRoom),t)],R).
   25do_test(test_np_box_2) :-  local_demo([holds_at(inRoom(lisa,livingRoom),t)],R).
   26do_test(test_np_box_3) :-  local_demo([holds_at(directlyIn(lisa,kitchen),t)],R).
   27
   28*/
   29%do_test(test_np_box_4) :-  local_demo([holds_at(inRoom(lisa,kitchen),t)],R).
   30
   31% fix this next test and the "test_np_box_occurs" should pass
   32%do_test(has_occured) :-  local_demo([has_occured(move(lisa,box,livingRoom,lisa))],R).
   33
   34% 
   35do_test(happened) :-  local_demo([happens(move(lisa,box,livingRoom,lisa),T)],R).
   36
   37do_test(happened2) :-  local_demo([happens(move(lisa,box,livingRoom,lisa),T1,T2)],R).
   38
   39% 
   40do_test(happend2b) :-  fail, local_demo(
   41              [happens(move(lisa,newspaper,livingRoom,box),t_plus_01),
   42                before(t_plus_01, t_plus_41),
   43               happens(move(lisa,lisa,kitchen,livingRoom),t_plus_41)],R).
   44
   45do_test(happend2a) :- fail,  local_demo(
   46              [happens(move(lisa,newspaper,livingRoom,box),t_plus_01,t_plus_02),
   47                before(t_plus_01, t_plus_41),
   48               happens(move(lisa,lisa,kitchen,livingRoom),t_plus_41,t_plus_42)],R).
   49
   50do_test(happend2r) :- fail, local_demo(
   51              [happens(move(lisa,newspaper,livingRoom,box),t_plus_01,t_plus_02),
   52                before(t_plus_41, t_plus_01),
   53               happens(move(lisa,lisa,kitchen,livingRoom),t_plus_41,t_plus_42)],R).
   54
   55
   56
   57do_test(test_np_box_occurs) :- test_np_box_occurs.
   58
   59test_np_box_occurs:- 
   60 findall(E, (ec_axiom(E,[]),functor(E,happens,_)), UHapsList),
   61 predsort(compare_on_time_arg,UHapsList,HapsList),
   62 dbginfo('HapsList'=HapsList), 
   63 /* 
   64   HapsList = 
   65         [happens(move(lisa,newspaper,livingRoom,box),0),
   66          happens(move(lisa,box,livingRoom,lisa),1),
   67          happens(move(lisa,lisa,livingRoom,kitchen),2),
   68          happens(move(lisa,box,lisa,kitchen),3),
   69          happens(move(lisa,lisa,kitchen,livingRoom),4)].
   70*/
   71
   72 make_falling_edges_v2(t_plus_, t_minus_1, HapsList, [_|Edges], _Out),
   73 dbginfo('Edges'=Edges), !,
   74 /*
   75   Edges = [holds_at(has_occured(move(lisa,newspaper,livingRoom,box)),t_plus_01),
   76            before(t_plus_01,t_plus_11),
   77            holds_at(has_occured(move(lisa,box,livingRoom,lisa)),t_plus_11),
   78            before(t_plus_11,t_plus_21),
   79            holds_at(has_occured(move(lisa,lisa,livingRoom,kitchen)),t_plus_21),
   80            before(t_plus_21,t_plus_31),
   81            holds_at(has_occured(move(lisa,box,lisa,kitchen)),
   82            t_plus_31),before(t_plus_31,t_plus_41),
   83            holds_at(has_occured(move(lisa,lisa,kitchen,livingRoom)),t_plus_41)].
   84
   85   Edges_V2 = [happens(move(lisa,newspaper,livingRoom,box),t_plus_01,t_plus_02),
   86               before(t_plus_02,t_plus_11),
   87               happens(move(lisa,box,livingRoom,lisa),t_plus_11,t_plus_12),
   88               before(t_plus_12,t_plus_21),
   89               happens(move(lisa,lisa,livingRoom,kitchen),t_plus_21,t_plus_22),
   90               before(t_plus_22,t_plus_31),
   91               happens(move(lisa,box,lisa,kitchen),t_plus_31,t_plus_32),
   92               before(t_plus_32,t_plus_41),
   93               happens(move(lisa,lisa,kitchen,livingRoom),t_plus_41,t_plus_42)].
   94   .
   95
   96
   97   Edges_T3 = [happens(move(lisa,newspaper,livingRoom,box),t_plus_01,t_plus_02),
   98               before(t_plus_01,t_plus_41),
   99               happens(move(lisa,lisa,kitchen,livingRoom),t_plus_41,t_plus_42)].
  100.
  101
  102
  103 */
  104 local_demo(Edges,_R),!.
  105
  106do_test(test_np_box_agent) :-  forall(do_test_gen(What), local_demo([holds_at(What,When)],R)).
  107
  108
  109/*
  110
  111Just to see the syntax (not related to this work)
  112
  113axiom(happens(shift_pack(Agnt,P,R1,R2,R3),T1,T6),
  114     [happens(go_to_room(Agnt,R1,R2),T1,T2),
  115     before(T2,T3), not(clipped(T2,atRoom(Agnt,R2),T3)), not(clipped(T1,inRoom(P,R2),T3)),
  116     happens(pick_up(Agnt,P),T3), before(T3,T4), happens(go_to_room(Agnt,R2,R3),T4,T5),
  117     before(T5,T6), not(clipped(T3,got(Agnt,P),T6)), not(clipped(T5,atRoom(Agnt,R3),T6)),
  118     happens(put_down(Agnt,P),T6)]).
  119
  120axiom(initiates(shift_pack(Agnt,P,R1,R2,R3),inRoom(P,R3),T),
  121     [holds_at(atRoom(Agnt,R1),T), holds_at(inRoom(P,R2),T)]).
  122*/
  123
  124axiom(happens(rise_and_fall(Event),T1,T3),
  125     [happens(begining(Event),T1), before(T1,T2), 
  126      happens(ocuring(Event),T2,T3),  before(T2,T3),
  127      % because its ocuring the begining not clipped?
  128      % not(clipped(T1,begun(Event),T2)),      
  129      happens(ending(Event),T3)]).
  130
  131axiom(terminates(begining(Event),holds_at( never_ocurred(Event),t),t), []).
  132axiom( initiates(begining(Event),holds_at(    just_begun(Event),t),t), []).
  133axiom(terminates( ocuring(Event),holds_at(    just_begun(Event),t),t), []).
  134axiom( initiates( ocuring(Event),holds_at(    now_occurs(Event),t),t), []).
  135axiom(terminates(  ending(Event),holds_at(    now_occurs(Event),t),t), []).
  136axiom( initiates(  ending(Event),holds_at(   has_occured(Event),t),t), []).
  137
  138axiom(initially( (never_ocurred(Event))),[]):- executable(Event).
  139axiom(initially( neg(just_begun(Event))),[]):- executable(Event).
  140axiom(initially( neg(now_occurs(Event))),[]):- executable(Event).
  141axiom(initially(neg(has_occured(Event))),[]):- executable(Event).
  142
  143%
  144%
  145% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  146% ; FILE: examples/Mueller2006/Chapter10/MovingNewspaperAndBox.e
  147% ; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  148% ;
  149% ; Copyright (c) 2005 IBM Corporation and others.
  150% ; All rights reserved. This program and the accompanying materials
  151% ; are made available under the terms of the Common Public License v1.0
  152% ; which accompanies this distribution, and is available in
  153% ; http://www.eclipse.org/legal/cpl-v10.html
  154% ;
  155% ; Contributors:
  156% ; IBM - Initial implementation
  157% ;
  158% ; @book{Mueller:2006,
  159% ;   author = "Erik T. Mueller",
  160% ;   year = "2006",
  161% ;   title = "Commonsense Reasoning",
  162% ;   address = "San Francisco",
  163% ;   publisher = "Morgan Kaufmann/Elsevier",
  164% ; }
  165% ;
  166
  167% ectest/TestBoxRoom.e:24
  168% load foundations/Root.e
  169% ectest/TestBoxRoom.e:25
  170
  171% ectest/TestBoxRoom.e:25
  172% ec_to_pl(do_ec_load, current_output, 'foundations/Root.e').
  173% ec_in_to_pl(do_ec_load, current_output, <stream>(0x55638dfaaab0)).
  174% ec_io(do_ec_load, <stream>(0x55638dfaaab0)).
  175% foundations/Root.e:1
  176
  177% ;
  178% ; Copyright (c) 2005 IBM Corporation and others.
  179% ; All rights reserved. This program and the accompanying materials
  180% ; are made available under the terms of the Common Public License v1.0
  181% ; which accompanies this distribution, and is available at
  182% ; http://www.eclipse.org/legal/cpl-v10.html
  183% ;
  184% ; Contributors:
  185% ; IBM - Initial implementation
  186% ;
  187% foundations/Root.e:11
  188% sort boolean
  189sort(boolean).
  190
  191% sort integer
  192sort(integer).
  193
  194% reified sort predicate
  195reified_sort(predicate).
  196
  197% reified sort function
  198reified_sort(function).
  199
  200%
  201% ; End of file.
  202% ectest/TestBoxRoom.e:25
  203% load foundations/EC.e
  204% ectest/TestBoxRoom.e:26
  205
  206% ectest/TestBoxRoom.e:26
  207% ec_to_pl(do_ec_load, current_output, 'foundations/EC.e').
  208% ec_in_to_pl(do_ec_load, current_output, <stream>(0x55638e470710)).
  209% ec_io(do_ec_load, <stream>(0x55638e470710)).
  210% foundations/EC.e:1
  211
  212% ;
  213% ; Copyright (c) 2005 IBM Corporation and others.
  214% ; All rights reserved. This program and the accompanying materials
  215% ; are made available under the terms of the Common Public License v1.0
  216% ; which accompanies this distribution, and is available at
  217% ; http://www.eclipse.org/legal/cpl-v10.html
  218% ;
  219% ; Contributors:
  220% ; IBM - Initial implementation
  221% ;
  222% ; Event Calculus (EC)
  223% ;
  224% ; @incollection{MillerShanahan:2002,
  225% ;   author = "Rob Miller and Murray Shanahan",
  226% ;   year = "2002",
  227% ;   title = "Some alternative formulations of the event calculus",
  228% ;   editor = "Antonis C. Kakas and Fariba Sadri",
  229% ;   booktitle = "Computational Logic: Logic Programming and Beyond: Essays in Honour of \uppercase{R}obert \uppercase{A}. \uppercase{K}owalski, Part \uppercase{II}",
  230% ;   series = "Lecture Notes in Computer Science",
  231% ;   volume = "2408",
  232% ;   pages = "452--490",
  233% ;   address = "Berlin",
  234% ;   publisher = "Springer",
  235% ; }
  236% ;
  237% foundations/EC.e:26
  238%
  239% sort time: integer
  240axiom(subsort(time,integer),[]).
  241
  242% sort offset: integer
  243axiom(subsort(offset,integer),[]).
  244
  245%
  246% reified sort fluent
  247reified_sort(fluent).
  248
  249% reified sort event
  250reified_sort(event).
  251
  252
  253% foundations/EC.e:32
  254%
  255% predicate Happens(event,time)
  256predicate(happens(event,time)).
  257
  258% predicate HoldsAt(fluent,time)
  259predicate(holds_at(fluent,time)).
  260
  261% predicate ReleasedAt(fluent,time)
  262predicate(releasedAt(fluent,time)).
  263
  264% predicate Initiates(event,fluent,time)
  265predicate(initiates(event,fluent,time)).
  266
  267% predicate Terminates(event,fluent,time)
  268predicate(terminates(event,fluent,time)).
  269
  270
  271% foundations/EC.e:38
  272% predicate Releases(event,fluent,time)
  273predicate(releases(event,fluent,time)).
  274
  275% predicate Trajectory(fluent,time,fluent,offset)
  276predicate(trajectory(fluent,time,fluent,offset)).
  277
  278%
  279% ; End of file.
  280% ectest/TestBoxRoom.e:26
  281%
  282% sort object
  283sort(object).
  284
  285% sort agent: object
  286axiom(subsort(agent,object),[]).
  287
  288% sort physobj: object
  289axiom(subsort(physobj,object),[]).
  290
  291% sort room: object
  292axiom(subsort(room,object),[]).
  293
  294%
  295% ectest/TestBoxRoom.e:32
  296fluent(directlyIn(object,object)).
  297
  298
  299%
  300fluent(inRoom(object,room)).
  301
  302%
  303% noninertial inRoom
  304noninertial(inRoom).
  305
  306%
  307executable(move(_agent,_object0,_object1,_object2)).
  308abducible(dummy).
  309%
  310% ectest/TestBoxRoom.e:38
  311% agent Lisa
  312isa(lisa,agent).
  313
  314% physobj Box, Newspaper
  315isa(box,physobj).
  316
  317
  318isa(newspaper,physobj).
  319
  320% room Kitchen, LivingRoom
  321isa(kitchen,room).
  322
  323
  324isa(livingRoom,room).
  325
  326
  327
  328%
  329% ; Sigma
  330%
  331% ; RS10
  332% ectest/TestBoxRoom.e:45
  333% [agent,physobj1,physobj2,room,time]%
  334% HoldsAt(directlyIn(agent,room),time) &
  335% HoldsAt(directlyIn(physobj1,room),time) &
  336% HoldsAt(inRoom(physobj2,room),time) ->
  337% Initiates(move(agent,physobj1,room,physobj2),directlyIn(physobj1,physobj2),time).
  338axiom(
  339  initiates(
  340    move(Agent,Physobj1,Room,Physobj2),
  341    directlyIn(Physobj1,Physobj2),Time),
  342   [holds_at(directlyIn(Agent,Room),Time),
  343    holds_at(directlyIn(Physobj1,Room),Time),
  344    holds_at(inRoom(Physobj2,Room),Time)]).
  345
  346%
  347%
  348% ; RS11
  349% ectest/TestBoxRoom.e:52
  350% [agent,physobj1,physobj2,room,time]%
  351% HoldsAt(directlyIn(agent,room),time) &
  352% HoldsAt(directlyIn(physobj1,room),time) &
  353% HoldsAt(inRoom(physobj2,room),time) ->
  354% Terminates(move(agent,physobj1,room,physobj2),directlyIn(physobj1,room),time).
  355axiom(terminates(move(Agent,Physobj1,Room,Physobj2),directlyIn(Physobj1,Room),Time),[holds_at(directlyIn(Agent,Room),Time),holds_at(directlyIn(Physobj1,Room),Time),holds_at(inRoom(Physobj2,Room),Time)]).
  356
  357%
  358%
  359% ; RS12
  360% ectest/TestBoxRoom.e:59
  361% [agent,physobj1,physobj2,room,time]%
  362% HoldsAt(directlyIn(agent,room),time) ->
  363% Initiates(move(agent,physobj1,physobj2,room),directlyIn(physobj1,room),time).
  364axiom(initiates(move(Agent,Physobj1,Physobj2,Room),directlyIn(Physobj1,Room),Time),[holds_at(directlyIn(Agent,Room),Time)]).
  365
  366%
  367%
  368% ; RS13
  369% ectest/TestBoxRoom.e:64
  370% [agent,physobj1,physobj2,room,time]%
  371% HoldsAt(directlyIn(agent,room),time) ->
  372% Terminates(move(agent,physobj1,physobj2,room),directlyIn(physobj1,physobj2),time).
  373axiom(terminates(move(Agent,Physobj1,Physobj2,Room),directlyIn(Physobj1,Physobj2),Time),[holds_at(directlyIn(Agent,Room),Time)]).
  374
  375%
  376%
  377% ; RS14
  378% ectest/TestBoxRoom.e:69
  379% [agent,room1,room2,time]%
  380% HoldsAt(directlyIn(agent,room1),time) ->
  381% Initiates(move(agent,agent,room1,room2),directlyIn(agent,room2),time).
  382axiom(initiates(move(Agent,Agent,Room1,Room2),directlyIn(Agent,Room2),Time),[holds_at(directlyIn(Agent,Room1),Time)]).
  383
  384%
  385%
  386% ; RS15
  387% ectest/TestBoxRoom.e:74
  388% [agent,room1,room2,time]%
  389% HoldsAt(directlyIn(agent,room1),time) ->
  390% Terminates(move(agent,agent,room1,room2),directlyIn(agent,room1),time).
  391axiom(terminates(move(Agent,Agent,Room1,Room2),directlyIn(Agent,Room1),Time),[holds_at(directlyIn(Agent,Room1),Time)]).
  392
  393%
  394%
  395% ; RS16
  396% ectest/TestBoxRoom.e:79
  397% [agent,physobj,room,time]%
  398% HoldsAt(directlyIn(agent,room),time) &
  399% HoldsAt(directlyIn(physobj,room),time) ->
  400% Initiates(move(agent,physobj,room,agent),directlyIn(physobj,agent),time).
  401axiom(initiates(move(Agent,Physobj,Room,Agent),directlyIn(Physobj,Agent),Time),[holds_at(directlyIn(Agent,Room),Time),holds_at(directlyIn(Physobj,Room),Time)]).
  402
  403%
  404%
  405% ; RS17
  406% ectest/TestBoxRoom.e:85
  407% [agent,physobj,room,time]%
  408% HoldsAt(directlyIn(agent,room),time) &
  409% HoldsAt(directlyIn(physobj,room),time) ->
  410% Terminates(move(agent,physobj,room,agent),directlyIn(physobj,room),time).
  411axiom(terminates(move(Agent,Physobj,Room,Agent),directlyIn(Physobj,Room),Time),[holds_at(directlyIn(Agent,Room),Time),holds_at(directlyIn(Physobj,Room),Time)]).
  412
  413%
  414%
  415% ; RS18
  416% ectest/TestBoxRoom.e:91
  417% [agent,physobj,room,time]%
  418% HoldsAt(directlyIn(physobj,agent),time) &
  419% HoldsAt(directlyIn(agent,room),time) ->
  420% Initiates(move(agent,physobj,agent,room),directlyIn(physobj,room),time).
  421axiom(initiates(move(Agent,Physobj,Agent,Room),directlyIn(Physobj,Room),Time),[holds_at(directlyIn(Physobj,Agent),Time),holds_at(directlyIn(Agent,Room),Time)]).
  422
  423%
  424%
  425% ; RS19
  426% ectest/TestBoxRoom.e:97
  427% [agent,physobj,room,time]%
  428% HoldsAt(directlyIn(physobj,agent),time) &
  429% HoldsAt(directlyIn(agent,room),time) ->
  430% Terminates(move(agent,physobj,agent,room),directlyIn(physobj,agent),time).
  431axiom(terminates(move(Agent,Physobj,Agent,Room),directlyIn(Physobj,Agent),Time),[holds_at(directlyIn(Physobj,Agent),Time),holds_at(directlyIn(Agent,Room),Time)]).
  432
  433%
  434%
  435% ; Delta
  436% ectest/TestBoxRoom.e:103
  437%
  438% Happens(move(Lisa,Newspaper,LivingRoom,Box),0).
  439axiom_hide(happens(move(lisa,newspaper,livingRoom,box),0),[]).
  440
  441%
  442% Happens(move(Lisa,Box,LivingRoom,Lisa),1).
  443axiom_hide(happens(move(lisa,box,livingRoom,lisa),1),[]).
  444
  445%
  446% Happens(move(Lisa,Lisa,LivingRoom,Kitchen),2).
  447axiom_hide(happens(move(lisa,lisa,livingRoom,kitchen),2),[]).
  448
  449%
  450% Happens(move(Lisa,Box,Lisa,Kitchen),3).
  451axiom_hide(happens(move(lisa,box,lisa,kitchen),3),[]).
  452
  453%
  454% Happens(move(Lisa,Lisa,Kitchen,LivingRoom),4).
  455axiom_hide(happens(move(lisa,lisa,kitchen,livingRoom),4),[]).
  456
  457%
  458% ectest/TestBoxRoom.e:109
  459%
  460% ; Psi
  461%
  462% ; RS1
  463% ectest/TestBoxRoom.e:113
  464% [object,time] % !HoldsAt(directlyIn(object,object),time).
  465axiom(holds_at(neg(directlyIn(Object,Object)),Time),[]).
  466
  467%
  468%
  469% ; RS2
  470% ectest/TestBoxRoom.e:116
  471% [object1,object2,time]%
  472% HoldsAt(directlyIn(object1,object2),time) ->
  473% !HoldsAt(directlyIn(object2,object1),time).
  474axiom(holds_at(neg(directlyIn(Object2,Object1)),Time),[holds_at(directlyIn(Object1,Object2),Time)]).
  475
  476%
  477%
  478% ; RS3
  479% ectest/TestBoxRoom.e:121
  480% [object1,object2,object3,time]%
  481% HoldsAt(directlyIn(object1,object2),time) &
  482% HoldsAt(directlyIn(object2,object3),time) ->
  483% !HoldsAt(directlyIn(object1,object3),time).
  484axiom(holds_at(neg(directlyIn(Object1,Object3)),Time),[holds_at(directlyIn(Object1,Object2),Time),holds_at(directlyIn(Object2,Object3),Time)]).
  485
  486%
  487%
  488% ; RS4
  489% ectest/TestBoxRoom.e:127
  490% [object,object1,object2,time]%
  491% HoldsAt(directlyIn(object,object1),time) &
  492% HoldsAt(directlyIn(object,object2),time) ->
  493% object1=object2.
  494axiom(Object1=Object2,[holds_at(directlyIn(Object,Object1),Time),holds_at(directlyIn(Object,Object2),Time)]).
  495
  496%
  497%
  498% ; RS7
  499% ectest/TestBoxRoom.e:133
  500% [object,room,time]%
  501% HoldsAt(directlyIn(object,room),time) ->
  502% HoldsAt(inRoom(object,room),time).
  503axiom(holds_at(inRoom(Object,Room),Time),[holds_at(directlyIn(Object,Room),Time)]).
  504
  505%
  506%
  507% ; RS8
  508% ectest/TestBoxRoom.e:138
  509% [object1,object2,room,time]%
  510% HoldsAt(directlyIn(object1,object2),time) &
  511% HoldsAt(inRoom(object2,room),time) ->
  512% HoldsAt(inRoom(object1,room),time).
  513axiom(holds_at(inRoom(Object1,Room),Time),[holds_at(directlyIn(Object1,Object2),Time),holds_at(inRoom(Object2,Room),Time)]).
  514
  515%
  516%
  517% ; RS9
  518% ectest/TestBoxRoom.e:144
  519% [object,room1,room2,time]%
  520% HoldsAt(inRoom(object,room1),time) &
  521% HoldsAt(inRoom(object,room2),time) ->
  522% room1=room2.
  523axiom(Room1=Room2,[holds_at(inRoom(Object,Room1),Time),holds_at(inRoom(Object,Room2),Time)]).
  524
  525%
  526%
  527% ; Gamma
  528% ectest/TestBoxRoom.e:150
  529%
  530% HoldsAt(directlyIn(Lisa,LivingRoom),0).
  531axiom(initially(directlyIn(lisa,livingRoom)),[]).
  532
  533%
  534% HoldsAt(directlyIn(Newspaper,LivingRoom),0).
  535axiom(initially(directlyIn(newspaper,livingRoom)),[]).
  536
  537%
  538% HoldsAt(directlyIn(Box,LivingRoom),0).
  539axiom(initially(directlyIn(box,livingRoom)),[]).
  540
  541%
  542%
  543% ; added:
  544% ectest/TestBoxRoom.e:156
  545% [room1,room2,time] % !HoldsAt(inRoom(room1,room2),time).
  546axiom(holds_at(neg(inRoom(Room1,Room2)),Time),[]).
  547
  548%
  549% ectest/TestBoxRoom.e:157
  550% [room,object,time] % !HoldsAt(directlyIn(room,object),time).
  551axiom(holds_at(neg(directlyIn(Room,Object)),Time),[]).
  552
  553%
  554%
  555% ; entailed:
  556% ; HoldsAt(directlyIn(Lisa,LivingRoom),5).
  557% ; HoldsAt(directlyIn(Box,Kitchen),5).
  558% ; HoldsAt(inRoom(Newspaper,Kitchen),5).
  559% ectest/TestBoxRoom.e:163
  560%
  561% completion Happens
  562completion(happens).
  563
  564%
  565% range time 0 5
  566range(time,0,5).
  567
  568% range offset 1 1
  569range(offset,1,1).
  570
  571%
  572% ; End of file.
  573% ectest/TestBoxRoom.e:170
  574%
  575%