1:-include(library('ec_planner/ec_test_incl')).    2:-expects_dialect(pfc).    3 %  loading(always,'ectest/ec_reader_test_examples.e').
    4%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    5%; FILE: examples/Mueller2004a/Holding.e
    6%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    7%;
    8%; Copyright (c) 2005 IBM Corporation and others.
    9%; All rights reserved. This program and the accompanying materials
   10%; are made available under the terms of the Common Public License v1.0
   11%; which accompanies this distribution, and is available at
   12%; http://www.eclipse.org/legal/cpl-v10.html
   13%;
   14%; Contributors:
   15%; IBM - Initial implementation
   16%;
   17%; @article{Mueller:2004a,
   18%;   author = "Erik T. Mueller",
   19%;   year = "2004",
   20%;   title = "Event calculus reasoning through satisfiability",
   21%;   journal = "Journal of Logic and Computation",
   22%;   volume = "14",
   23%;   number = "5",
   24%;   pages = "703--730",
   25%; }
   26%;
   27
   28% option encoding 3
   29:- set_ec_option(encoding, 3).   30
   31% load foundations/Root.e
   32
   33% load foundations/EC.e
   34
   35% sort person
   36==> sort(person).
   37
   38% sort object
   39==> sort(object).
   40
   41% event Hold(person,object)
   42 %  event(hold(person,object)).
   43==> mpred_prop(hold(person,object),event).
   44==> meta_argtypes(hold(person,object)).
   45
   46% fluent Holding(person,object)
   47 %  fluent(holding(person,object)).
   48==> mpred_prop(holding(person,object),fluent).
   49==> meta_argtypes(holding(person,object)).
   50
   51% person P1
   52==> t(person,p1).
   53
   54% object O1
   55==> t(object,o1).
   56
   57
   58% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:41
   59% Happens(Hold(P1,O1),0).
   60axiom(happens(hold(p1, o1), t),
   61    [is_time(0)]).
   62
   63
   64% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:43
   65% [person,object,time]
   66% Initiates(Hold(person,object),Holding(person,object),time).
   67% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:44
   68axiom(initiates(hold(Person, Object), holding(Person, Object), Time),
   69    []).
   70
   71
   72% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:46
   73% !HoldsAt(Holding(P1,O1),0).
   74 %  not(initially(holding(p1,o1))).
   75axiom(not(initially(holding(p1, o1))),
   76    []).
   77
   78
   79% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:47
   80%;;; AUTO !ReleasedAt(Holding(P1,O1),0).
   81
   82% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:49
   83% completion Happens
   84% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:50
   85==> completion(happens).
   86
   87% range time 0 1
   88% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:52
   89==> range(time,0,1).
   90
   91% range offset 1 1
   92% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:53
   93==> range(offset,1,1).
   94%; End of file.
   95%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
   96%; FILE: examples/Mueller2004a/Leaf.e
   97%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
   98%;
   99%; Copyright (c) 2005 IBM Corporation and others.
  100%; All rights reserved. This program and the accompanying materials
  101%; are made available under the terms of the Common Public License v1.0
  102%; which accompanies this distribution, and is available at
  103%; http://www.eclipse.org/legal/cpl-v10.html
  104%;
  105%; Contributors:
  106%; IBM - Initial implementation
  107%;
  108%; @article{Mueller:2004a,
  109%;   author = "Erik T. Mueller",
  110%;   year = "2004",
  111%;   title = "Event calculus reasoning through satisfiability",
  112%;   journal = "Journal of Logic and Computation",
  113%;   volume = "14",
  114%;   number = "5",
  115%;   pages = "703--730",
  116%; }
  117%;
  118
  119% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:82
  120% option trajectory on
  121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:83
  122:- set_ec_option(trajectory, on).  123
  124% load foundations/Root.e
  125
  126% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:85
  127% load foundations/EC.e
  128
  129% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:87
  130% sort object
  131% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:88
  132==> sort(object).
  133
  134% sort height: integer
  135% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:89
  136==> subsort(height,integer).
  137
  138% fluent Height(object,height)
  139 %  fluent(height(object,height)).
  140% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:91
  141==> mpred_prop(height(object,height),fluent).
  142==> meta_argtypes(height(object,height)).
  143
  144% fluent Falling(object)
  145 %  fluent(falling(object)).
  146% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:92
  147==> mpred_prop(falling(object),fluent).
  148==> meta_argtypes(falling(object)).
  149
  150% event StartFalling(object)
  151 %  event(startFalling(object)).
  152% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:93
  153==> mpred_prop(startFalling(object),event).
  154==> meta_argtypes(startFalling(object)).
  155
  156% event HitsGround(object)
  157 %  event(hitsGround(object)).
  158% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:94
  159==> mpred_prop(hitsGround(object),event).
  160==> meta_argtypes(hitsGround(object)).
  161
  162
  163% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:95
  164% [object,height1,height2,time]
  165% HoldsAt(Height(object,height1),time) &
  166% HoldsAt(Height(object,height2),time) ->
  167% height1=height2.
  168% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:98
  169axiom(Height1=Height2,
  170   
  171    [ holds_at(height(Object, Height1), Time),
  172      holds_at(height(Object, Height2), Time)
  173    ]).
  174
  175
  176% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:100
  177% [object,time]
  178% Initiates(StartFalling(object),Falling(object),time).
  179% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:101
  180axiom(initiates(startFalling(Object), falling(Object), Time),
  181    []).
  182
  183
  184% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:103
  185% [object,height,time]
  186% Releases(StartFalling(object),Height(object,height),time).
  187% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:104
  188axiom(releases(startFalling(Object), height(Object, Height), Time),
  189    []).
  190
  191
  192% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:106
  193% [object,height1,height2,offset,time]
  194% HoldsAt(Height(object,height1),time) &
  195% height2=height1-offset*offset ->
  196% Trajectory(Falling(object),time,Height(object,height2),offset).
  197% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:109
  198axiom(trajectory(falling(Object), Time, height(Object, Height2), Offset),
  199   
  200    [ holds_at(height(Object, Height1), Time),
  201      equals(Height2, Height1-Offset*Offset)
  202    ]).
  203
  204
  205% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:111
  206% [object,time]
  207% HoldsAt(Falling(object),time) &
  208% HoldsAt(Height(object,0),time) ->
  209% Happens(HitsGround(object),time).
  210% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:114
  211axiom(happens(hitsGround(Object), Time),
  212   
  213    [ holds_at(falling(Object), Time),
  214      holds_at(height(Object, 0), Time)
  215    ]).
  216
  217
  218% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:116
  219%;[object,height1,height2,time]
  220%;HoldsAt(Height(object,height1),time) &
  221%;height1 != height2 ->
  222%;Terminates(HitsGround(object),Height(object,height2),time).
  223% [object,height,time]
  224% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:122
  225% HoldsAt(Height(object,height),time) ->
  226% Initiates(HitsGround(object),Height(object,height),time).
  227% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:123
  228axiom(initiates(hitsGround(Object), height(Object, Height), Time),
  229    [holds_at(height(Object, Height), Time)]).
  230
  231
  232% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:125
  233% [object,time]
  234% Terminates(HitsGround(object),Falling(object),time).
  235% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:126
  236axiom(terminates(hitsGround(Object), falling(Object), Time),
  237    []).
  238
  239% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:128
  240% object Leaf
  241% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:129
  242==> t(object,leaf).
  243
  244
  245% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:130
  246% !HoldsAt(Falling(Leaf),0).
  247 %  not(initially(falling(leaf))).
  248axiom(not(initially(falling(leaf))),
  249    []).
  250
  251
  252% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:131
  253% HoldsAt(Height(Leaf,9),0).
  254axiom(initially(height(leaf, 9)),
  255    []).
  256
  257
  258% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:132
  259% Happens(StartFalling(Leaf),0).
  260axiom(happens(startFalling(leaf), t),
  261    [is_time(0)]).
  262
  263% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:134
  264% completion Happens
  265% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:135
  266==> completion(happens).
  267
  268% range time 0 4
  269% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:137
  270==> range(time,0,4).
  271
  272% range offset 1 9
  273% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:138
  274==> range(offset,1,9).
  275
  276% range height 0 9
  277% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:139
  278==> range(height,0,9).
  279%; End of file.
  280%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  281%; FILE: examples/Cassimatis2002/PolySpace.e
  282%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  283%;
  284%; Copyright (c) 2005 IBM Corporation and others.
  285%; All rights reserved. This program and the accompanying materials
  286%; are made available under the terms of the Common Public License v1.0
  287%; which accompanies this distribution, and is available at
  288%; http://www.eclipse.org/legal/cpl-v10.html
  289%;
  290%; Contributors:
  291%; IBM - Initial implementation
  292%;
  293%; @phdthesis{Cassimatis:2002,
  294%;   author = "Nicholas L. Cassimatis",
  295%;   year = "2002",
  296%;   title = "Polyscheme: A Cognitive Architecture for Integrating Multiple Representation and Inference Schemes",
  297%;   address = "Cambridge, MA",
  298%;   school = "Program in Media Arts and Sciences, School of Architecture and Planning, Massachusetts Institute of Technology",
  299%; }
  300%;
  301%; sorts
  302
  303% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:167
  304% sort object
  305% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:168
  306==> sort(object).
  307
  308% sort xcoord: integer
  309% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:169
  310==> subsort(xcoord,integer).
  311
  312% sort ycoord: integer
  313% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:170
  314==> subsort(ycoord,integer).
  315
  316% sort grid
  317% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:171
  318==> sort(grid).
  319
  320% sort shape
  321% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:172
  322==> sort(shape).
  323
  324% sort color
  325% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:173
  326==> sort(color).
  327%; constants
  328
  329% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:175
  330% shape Round,Square
  331% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:176
  332==> t(shape,round).
  333==> t(shape,square).
  334
  335% color Red,Green
  336% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:177
  337==> t(color,red).
  338==> t(color,green).
  339%; predicates, fluents, and events
  340
  341% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:179
  342% predicate Equal(object,object)
  343 %  predicate(equal(object,object)).
  344% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:180
  345==> mpred_prop(equal(object,object),predicate).
  346==> meta_argtypes(equal(object,object)).
  347
  348% predicate Shape(object,shape)
  349 %  predicate(shape(object,shape)).
  350% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:181
  351==> mpred_prop(shape(object,shape),predicate).
  352==> meta_argtypes(shape(object,shape)).
  353
  354% predicate Color(object,color)
  355 %  predicate(color(object,color)).
  356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:182
  357==> mpred_prop(color(object,color),predicate).
  358==> meta_argtypes(color(object,color)).
  359
  360% fluent Location(grid,object,xcoord,ycoord)
  361 %  fluent(location(grid,object,xcoord,ycoord)).
  362% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:183
  363==> mpred_prop(location(grid,object,xcoord,ycoord),fluent).
  364==> meta_argtypes(location(grid,object,xcoord,ycoord)).
  365
  366% event Move(grid,object,xcoord,ycoord,xcoord,ycoord)
  367 %  event(move(grid,object,xcoord,ycoord,xcoord,ycoord)).
  368% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:184
  369==> mpred_prop(move(grid,object,xcoord,ycoord,xcoord,ycoord),event).
  370==> meta_argtypes(move(grid,object,xcoord,ycoord,xcoord,ycoord)).
  371
  372
  373% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:185
  374%; axioms
  375% [object1,object2]
  376 % Equal(object1,object2) -> Equal(object2,object1).
  377% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:187
  378axiom(equal(Object2, Object1),
  379    [equal(Object1, Object2)]).
  380
  381
  382% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:189
  383%; objects have unique shape
  384% [object,shape1,shape2]
  385% Shape(object,shape1) & Shape(object,shape2) ->
  386% shape1=shape2.
  387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:192
  388axiom(Shape1=Shape2,
  389    [shape(Object, Shape1), shape(Object, Shape2)]).
  390
  391
  392% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:194
  393%; objects have unique color
  394% [object,color1,color2]
  395% Color(object,color1) & Color(object,color2) ->
  396% color1=color2.
  397% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:197
  398axiom(Color1=Color2,
  399    [color(Object, Color1), color(Object, Color2)]).
  400
  401
  402% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:199
  403%; if objects are the same, they have the same shape
  404% [object1,object2]
  405% Equal(object1,object2) ->
  406% ({shape} Shape(object1,shape) & Shape(object2,shape)).
  407
  408 /*   if(equal(Object1, Object2),
  409         exists([Shape],
  410                 (shape(Object1, Shape), shape(Object2, Shape)))).
  411 */
  412
  413 /*  not(equal(Equal_Param, Shape_Param)) :-
  414       (   not(shape(Equal_Param, Shape_Ret))
  415       ;   not(shape(Shape_Param, Shape_Ret))
  416       ).
  417 */
  418% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:202
  419axiom(not(equal(Equal_Param, Shape_Param)),
  420    [not(shape(Equal_Param, Shape_Ret))]).
  421axiom(not(equal(Equal_Param, Shape_Param)),
  422    [not(shape(Shape_Param, Shape_Ret))]).
  423
  424 /*  shape(Shape_Param6, Shape_Ret7) :-
  425       equal(Shape_Param6, Equal_Ret).
  426 */
  427axiom(shape(Shape_Param6, Shape_Ret7),
  428    [equal(Shape_Param6, Equal_Ret)]).
  429
  430 /*  shape(Shape_Param9, Shape_Ret11) :-
  431       equal(Equal_Param10, Shape_Param9).
  432 */
  433axiom(shape(Shape_Param9, Shape_Ret11),
  434    [equal(Equal_Param10, Shape_Param9)]).
  435
  436
  437% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:204
  438%; if objects are the same, they have the same color
  439% [object1,object2]
  440% Equal(object1,object2) ->
  441% ({color} Color(object1,color) & Color(object2,color)).
  442
  443 /*   if(equal(Object1, Object2),
  444         exists([Color],
  445                 (color(Object1, Color), color(Object2, Color)))).
  446 */
  447
  448 /*  not(equal(Equal_Param, Color_Param)) :-
  449       (   not(color(Equal_Param, Color_Ret))
  450       ;   not(color(Color_Param, Color_Ret))
  451       ).
  452 */
  453% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:207
  454axiom(not(equal(Equal_Param, Color_Param)),
  455    [not(color(Equal_Param, Color_Ret))]).
  456axiom(not(equal(Equal_Param, Color_Param)),
  457    [not(color(Color_Param, Color_Ret))]).
  458
  459 /*  color(Color_Param6, Color_Ret7) :-
  460       equal(Color_Param6, Equal_Ret).
  461 */
  462axiom(color(Color_Param6, Color_Ret7),
  463    [equal(Color_Param6, Equal_Ret)]).
  464
  465 /*  color(Color_Param9, Color_Ret11) :-
  466       equal(Equal_Param10, Color_Param9).
  467 */
  468axiom(color(Color_Param9, Color_Ret11),
  469    [equal(Equal_Param10, Color_Param9)]).
  470
  471
  472% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:209
  473%; if objects are the same, they have the same location
  474% [grid,object1,object2,xcoord1,ycoord1,xcoord2,ycoord2,time]
  475% Equal(object1,object2) ->
  476% (HoldsAt(Location(grid,object1,xcoord1,ycoord1),time) &
  477%  HoldsAt(Location(grid,object2,xcoord2,ycoord2),time) ->
  478%  xcoord1=xcoord2 & ycoord1=ycoord2).
  479
  480 /*   if(equal(Object1, Object2),
  481         if((holds_at(location(Grid, Object1, Xcoord1, Ycoord1), Time), holds_at(location(Grid, Object2, Xcoord2, Ycoord2), Time)),
  482             (Xcoord1=Xcoord2, Ycoord1=Ycoord2))).
  483 */
  484
  485 /*  not(equal(Equal_Param, Equal_Ret)) :-
  486       ( holds_at(location(Location_Param,
  487                           Equal_Param,
  488                           Equals_Param,
  489                           Equals_Param12),
  490                  Time8),
  491         holds_at(location(Location_Param,
  492                           Equal_Ret,
  493                           Equals_Ret,
  494                           Location_Ret),
  495                  Time8)
  496       ),
  497       (   not(equals(Equals_Param, Equals_Ret))
  498       ;   not(equals(Equals_Param12, Location_Ret))
  499       ).
  500 */
  501% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:214
  502axiom(not(equal(Equal_Param, Equal_Ret)),
  503   
  504    [ not(equals(Equals_Param, Equals_Ret)),
  505      holds_at(location(Location_Param,
  506                        Equal_Param,
  507                        Equals_Param,
  508                        Equals_Param12),
  509               Time8),
  510      holds_at(location(Location_Param,
  511                        Equal_Ret,
  512                        Equals_Ret,
  513                        Location_Ret),
  514               Time8)
  515    ]).
  516axiom(not(equal(Equal_Param, Equal_Ret)),
  517   
  518    [ not(equals(Equals_Param12, Location_Ret)),
  519      holds_at(location(Location_Param,
  520                        Equal_Param,
  521                        Equals_Param,
  522                        Equals_Param12),
  523               Time8),
  524      holds_at(location(Location_Param,
  525                        Equal_Ret,
  526                        Equals_Ret,
  527                        Location_Ret),
  528               Time8)
  529    ]).
  530
  531 /*  not(holds_at(location(Location_Param17, Equal_Param20, Equals_Param18, Equals_Param19), Time16)) :-
  532       holds_at(location(Location_Param17,
  533                         Equal_Ret23,
  534                         Equals_Ret22,
  535                         Location_Ret21),
  536                Time16),
  537       (   not(equals(Equals_Param18, Equals_Ret22))
  538       ;   not(equals(Equals_Param19, Location_Ret21))
  539       ),
  540       equal(Equal_Param20, Equal_Ret23).
  541 */
  542axiom(not(holds_at(location(Location_Param17, Equal_Param20, Equals_Param18, Equals_Param19), Time16)),
  543   
  544    [ not(equals(Equals_Param18, Equals_Ret22)),
  545      holds_at(location(Location_Param17,
  546                        Equal_Ret23,
  547                        Equals_Ret22,
  548                        Location_Ret21),
  549               Time16),
  550      equal(Equal_Param20, Equal_Ret23)
  551    ]).
  552axiom(not(holds_at(location(Location_Param17, Equal_Param20, Equals_Param18, Equals_Param19), Time16)),
  553   
  554    [ not(equals(Equals_Param19, Location_Ret21)),
  555      holds_at(location(Location_Param17,
  556                        Equal_Ret23,
  557                        Equals_Ret22,
  558                        Location_Ret21),
  559               Time16),
  560      equal(Equal_Param20, Equal_Ret23)
  561    ]).
  562
  563 /*  not(holds_at(location(Location_Param25, Equal_Ret31, Equals_Ret30, Location_Ret29), Time24)) :-
  564       holds_at(location(Location_Param25,
  565                         Equal_Param28,
  566                         Equals_Param26,
  567                         Equals_Param27),
  568                Time24),
  569       (   not(equals(Equals_Param26, Equals_Ret30))
  570       ;   not(equals(Equals_Param27, Location_Ret29))
  571       ),
  572       equal(Equal_Param28, Equal_Ret31).
  573 */
  574axiom(not(holds_at(location(Location_Param25, Equal_Ret31, Equals_Ret30, Location_Ret29), Time24)),
  575   
  576    [ not(equals(Equals_Param26, Equals_Ret30)),
  577      holds_at(location(Location_Param25,
  578                        Equal_Param28,
  579                        Equals_Param26,
  580                        Equals_Param27),
  581               Time24),
  582      equal(Equal_Param28, Equal_Ret31)
  583    ]).
  584axiom(not(holds_at(location(Location_Param25, Equal_Ret31, Equals_Ret30, Location_Ret29), Time24)),
  585   
  586    [ not(equals(Equals_Param27, Location_Ret29)),
  587      holds_at(location(Location_Param25,
  588                        Equal_Param28,
  589                        Equals_Param26,
  590                        Equals_Param27),
  591               Time24),
  592      equal(Equal_Param28, Equal_Ret31)
  593    ]).
  594
  595 /*  equals(Equals_Param33, Equals_Ret36) :-
  596       ( holds_at(location(Location_Param34,
  597                           Equal_Param35,
  598                           Equals_Param33,
  599                           Location_Ret37),
  600                  Time32),
  601         holds_at(location(Location_Param34,
  602                           Equal_Ret39,
  603                           Equals_Ret36,
  604                           Location_Ret38),
  605                  Time32)
  606       ),
  607       equal(Equal_Param35, Equal_Ret39).
  608 */
  609axiom(equals(Equals_Param33, Equals_Ret36),
  610   
  611    [ holds_at(location(Location_Param34,
  612                        Equal_Param35,
  613                        Equals_Param33,
  614                        Location_Ret37),
  615               Time32),
  616      holds_at(location(Location_Param34,
  617                        Equal_Ret39,
  618                        Equals_Ret36,
  619                        Location_Ret38),
  620               Time32),
  621      equal(Equal_Param35, Equal_Ret39)
  622    ]).
  623
  624 /*  equals(Equals_Param41, Equals_Ret44) :-
  625       ( holds_at(location(Location_Param42,
  626                           Equal_Param43,
  627                           _,
  628                           Equals_Param41),
  629                  Time40),
  630         holds_at(location(Location_Param42,
  631                           Equal_Ret45,
  632                           _,
  633                           Equals_Ret44),
  634                  Time40)
  635       ),
  636       equal(Equal_Param43, Equal_Ret45).
  637 */
  638axiom(equals(Equals_Param41, Equals_Ret44),
  639   
  640    [ holds_at(location(Location_Param42,
  641                        Equal_Param43,
  642                        _,
  643                        Equals_Param41),
  644               Time40),
  645      holds_at(location(Location_Param42,
  646                        Equal_Ret45,
  647                        _,
  648                        Equals_Ret44),
  649               Time40),
  650      equal(Equal_Param43, Equal_Ret45)
  651    ]).
  652
  653
  654% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:216
  655%; object in one location at a time
  656% [grid,object,xcoord1,ycoord1,xcoord2,ycoord2,time]
  657% HoldsAt(Location(grid,object,xcoord1,ycoord1),time) &
  658% HoldsAt(Location(grid,object,xcoord2,ycoord2),time) ->
  659% xcoord1=xcoord2 & ycoord1=ycoord2.
  660
  661 /*   if((holds_at(location(Grid, Object, Xcoord1, Ycoord1), Time), holds_at(location(Grid, Object, Xcoord2, Ycoord2), Time)),
  662          (Xcoord1=Xcoord2, Ycoord1=Ycoord2)).
  663 */
  664
  665 /*  not(holds_at(location(Location_Param, A, Equals_Param, Equals_Param10), Time7)) :-
  666       holds_at(location(Location_Param,
  667                         A,
  668                         Equals_Ret,
  669                         Location_Ret),
  670                Time7),
  671       (   not(equals(Equals_Param, Equals_Ret))
  672       ;   not(equals(Equals_Param10, Location_Ret))
  673       ).
  674 */
  675% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:220
  676axiom(not(holds_at(location(Location_Param, A, Equals_Param, Equals_Param10), Time7)),
  677   
  678    [ not(equals(Equals_Param, Equals_Ret)),
  679      holds_at(location(Location_Param,
  680                        A,
  681                        Equals_Ret,
  682                        Location_Ret),
  683               Time7)
  684    ]).
  685axiom(not(holds_at(location(Location_Param, A, Equals_Param, Equals_Param10), Time7)),
  686   
  687    [ not(equals(Equals_Param10, Location_Ret)),
  688      holds_at(location(Location_Param,
  689                        A,
  690                        Equals_Ret,
  691                        Location_Ret),
  692               Time7)
  693    ]).
  694
  695 /*  not(holds_at(location(Location_Param14, A, Equals_Ret18, Location_Ret17), Time13)) :-
  696       holds_at(location(Location_Param14,
  697                         A,
  698                         Equals_Param15,
  699                         Equals_Param16),
  700                Time13),
  701       (   not(equals(Equals_Param15, Equals_Ret18))
  702       ;   not(equals(Equals_Param16, Location_Ret17))
  703       ).
  704 */
  705axiom(not(holds_at(location(Location_Param14, A, Equals_Ret18, Location_Ret17), Time13)),
  706   
  707    [ not(equals(Equals_Param15, Equals_Ret18)),
  708      holds_at(location(Location_Param14,
  709                        A,
  710                        Equals_Param15,
  711                        Equals_Param16),
  712               Time13)
  713    ]).
  714axiom(not(holds_at(location(Location_Param14, A, Equals_Ret18, Location_Ret17), Time13)),
  715   
  716    [ not(equals(Equals_Param16, Location_Ret17)),
  717      holds_at(location(Location_Param14,
  718                        A,
  719                        Equals_Param15,
  720                        Equals_Param16),
  721               Time13)
  722    ]).
  723
  724 /*  equals(Equals_Param20, Equals_Ret22) :-
  725       holds_at(location(Location_Param21,
  726                         A,
  727                         Equals_Param20,
  728                         Location_Ret23),
  729                Time19),
  730       holds_at(location(Location_Param21,
  731                         A,
  732                         Equals_Ret22,
  733                         Location_Ret24),
  734                Time19).
  735 */
  736axiom(equals(Equals_Param20, Equals_Ret22),
  737   
  738    [ holds_at(location(Location_Param21,
  739                        A,
  740                        Equals_Param20,
  741                        Location_Ret23),
  742               Time19),
  743      holds_at(location(Location_Param21,
  744                        A,
  745                        Equals_Ret22,
  746                        Location_Ret24),
  747               Time19)
  748    ]).
  749
  750 /*  equals(Equals_Param26, Equals_Ret28) :-
  751       holds_at(location(Location_Param27,
  752                         A,
  753                         _,
  754                         Equals_Param26),
  755                Time25),
  756       holds_at(location(Location_Param27,
  757                         A,
  758                         _,
  759                         Equals_Ret28),
  760                Time25).
  761 */
  762axiom(equals(Equals_Param26, Equals_Ret28),
  763   
  764    [ holds_at(location(Location_Param27,
  765                        A,
  766                        _,
  767                        Equals_Param26),
  768               Time25),
  769      holds_at(location(Location_Param27,
  770                        A,
  771                        _,
  772                        Equals_Ret28),
  773               Time25)
  774    ]).
  775
  776
  777% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:222
  778%; objects have locations
  779% [grid,object,time]
  780% (
  781% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:224
  782% {xcoord,ycoord} HoldsAt(Location(grid,object,xcoord,ycoord),time)).
  783
  784 /*  exists([Xcoord,Ycoord],
  785          holds_at(location(Grid,
  786   			 Object,
  787   			 Xcoord,
  788   			 Ycoord),
  789   		Time)).
  790 */
  791axiom(holds_at(location(Location_Param, _, _, Location_Ret), Time5),
  792    []).
  793
  794
  795% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:226
  796%; different objects are not at same location
  797% [grid,object1,object2,xcoord1,ycoord1,time]
  798% HoldsAt(Location(grid,object1,xcoord1,ycoord1),time) &
  799% HoldsAt(Location(grid,object2,xcoord1,ycoord1),time) ->
  800% Equal(object1,object2).
  801% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:230
  802axiom(equal(Object1, Object2),
  803   
  804    [ holds_at(location(Grid, Object1, Xcoord1, Ycoord1),
  805               Time),
  806      holds_at(location(Grid, Object2, Xcoord1, Ycoord1),
  807               Time)
  808    ]).
  809
  810
  811% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:232
  812%; moving to a location causes an object to be at that location
  813% [grid,object,xcoord1,ycoord1,xcoord2,ycoord2,time]
  814% Initiates(Move(grid,object,xcoord1,ycoord1,xcoord2,ycoord2),
  815%           Location(grid,object,xcoord2,ycoord2),
  816%           time).
  817% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:236
  818axiom(initiates(move(Grid, Object, Xcoord1, Ycoord1, Xcoord2, Ycoord2), location(Grid, Object, Xcoord2, Ycoord2), Time),
  819    []).
  820
  821
  822% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:238
  823%; moving to a location causes the object no longer to be at its previous
  824%; location
  825% [grid,object,xcoord1,ycoord1,xcoord2,ycoord2,time]
  826% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:241
  827% Terminates(Move(grid,object,xcoord1,ycoord1,xcoord2,ycoord2),
  828%            Location(grid,object,xcoord1,ycoord1),
  829%            time).
  830% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:243
  831axiom(terminates(move(Grid, Object, Xcoord1, Ycoord1, Xcoord2, Ycoord2), location(Grid, Object, Xcoord1, Ycoord1), Time),
  832    []).
  833
  834
  835% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:245
  836%;; allow diagonal movements
  837%;[grid,object,xcoord1,ycoord1,xcoord2,ycoord2,time]
  838%;Happens(Move(grid,object,xcoord1,ycoord1,xcoord2,ycoord2),time) ->
  839%;HoldsAt(Location(grid,object,xcoord1,ycoord1),time) &
  840%;(xcoord1=xcoord2 |
  841%; xcoord1=xcoord2+1 |
  842%; xcoord1=xcoord2-1) &
  843%;(ycoord1=ycoord2 |
  844%; ycoord1=ycoord2+1 |
  845%; ycoord1=ycoord2-1).
  846%; only allow right angle movements
  847% [grid,object,xcoord1,ycoord1,xcoord2,ycoord2,time]
  848% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:258
  849% Happens(Move(grid,object,xcoord1,ycoord1,xcoord2,ycoord2),time) ->
  850% HoldsAt(Location(grid,object,xcoord1,ycoord1),time) &
  851% ((xcoord1=xcoord2 & (ycoord1=ycoord2+1 | ycoord1=ycoord2-1)) |
  852%  (ycoord1=ycoord2 & (xcoord1=xcoord2+1 | xcoord1=xcoord2-1))).
  853% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:261
  854axiom(requires(move(Grid, Object, Xcoord1, Ycoord1, Xcoord2, Ycoord2), Time),
  855   
  856    [ equals(Ycoord1, Ycoord2+1),
  857      equals(Xcoord1, Xcoord2),
  858      holds_at(location(Grid, Object, Xcoord1, Ycoord1),
  859               Time)
  860    ]).
  861axiom(requires(move(Grid, Object, Xcoord1, Ycoord1, Xcoord2, Ycoord2), Time),
  862   
  863    [ equals(Ycoord1, Ycoord2-1),
  864      equals(Xcoord1, Xcoord2),
  865      holds_at(location(Grid, Object, Xcoord1, Ycoord1),
  866               Time)
  867    ]).
  868axiom(requires(move(Grid, Object, Xcoord1, Ycoord1, Xcoord2, Ycoord2), Time),
  869   
  870    [ equals(Xcoord1, Xcoord2+1),
  871      equals(Ycoord1, Ycoord2),
  872      holds_at(location(Grid, Object, Xcoord1, Ycoord1),
  873               Time)
  874    ]).
  875axiom(requires(move(Grid, Object, Xcoord1, Ycoord1, Xcoord2, Ycoord2), Time),
  876   
  877    [ equals(Xcoord1, Xcoord2-1),
  878      equals(Ycoord1, Ycoord2),
  879      holds_at(location(Grid, Object, Xcoord1, Ycoord1),
  880               Time)
  881    ]).
  882
  883
  884% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:263
  885%; End of file.
  886%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  887%; FILE: examples/Cassimatis2002/TwoScreens.e
  888%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
  889%;
  890%; Copyright (c) 2005 IBM Corporation and others.
  891%; All rights reserved. This program and the accompanying materials
  892%; are made available under the terms of the Common Public License v1.0
  893%; which accompanies this distribution, and is available at
  894%; http://www.eclipse.org/legal/cpl-v10.html
  895%;
  896%; Contributors:
  897%; IBM - Initial implementation
  898%;
  899%; @phdthesis{Cassimatis:2002,
  900%;   author = "Nicholas L. Cassimatis",
  901%;   year = "2002",
  902%;   title = "Polyscheme: A Cognitive Architecture for Integrating Multiple Representation and Inference Schemes",
  903%;   address = "Cambridge, MA",
  904%;   school = "Program in Media Arts and Sciences, School of Architecture and Planning, Massachusetts Institute of Technology",
  905%; }
  906%;
  907
  908% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:289
  909% load foundations/Root.e
  910
  911% load foundations/EC.e
  912
  913% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:291
  914% load examples/Cassimatis2002/PolySpace.e
  915
  916% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:293
  917% grid G1
  918% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:294
  919==> t(grid,g1).
  920
  921% object X,Y,Screen1,Screen2
  922% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:295
  923==> t(object,x).
  924==> t(object,y).
  925==> t(object,screen1).
  926==> t(object,screen2).
  927%; perceptions:
  928
  929
  930% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:297
  931% Shape(X,Round).
  932shape(x,round).
  933
  934
  935% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:298
  936% Color(X,Red).
  937color(x,red).
  938
  939
  940% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:299
  941% Shape(Y,Round).
  942shape(y,round).
  943
  944
  945% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:300
  946% Color(Y,Red).
  947color(y,red).
  948
  949
  950% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:301
  951% Shape(Screen1,Square).
  952shape(screen1,square).
  953
  954
  955% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:302
  956% Color(Screen1,Green).
  957color(screen1,green).
  958
  959
  960% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:303
  961% Shape(Screen2,Square).
  962shape(screen2,square).
  963
  964
  965% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:304
  966% Color(Screen2,Green).
  967color(screen2,green).
  968
  969
  970% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:305
  971% [time]
  972 % HoldsAt(Location(G1,Screen1,2,0),time).
  973holds_at(location(g1,screen1,2,0),Time).
  974
  975
  976% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:306
  977% [time]
  978 % HoldsAt(Location(G1,Screen2,4,0),time).
  979holds_at(location(g1,screen2,4,0),Time).
  980
  981
  982% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:307
  983% HoldsAt(Location(G1,X,1,1),0).
  984axiom(initially(location(g1, x, 1, 1)),
  985    []).
  986
  987
  988% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:308
  989% HoldsAt(Location(G1,Y,5,1),4).
  990holds_at(location(g1,y,5,1),4).
  991
  992
  993% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:310
  994% [xcoord,ycoord,time]
  995% xcoord!=% 2 & xcoord!=4 & !(xcoord=1 & ycoord=1 & time=0) ->
  996% !HoldsAt(Location(G1,X,xcoord,ycoord),time) |
  997% xcoord=5 & ycoord=1 & time=4 & Equal(X,Y).
  998
  999 /*   if(({dif(Xcoord, 2)}, {dif(Xcoord, 4)}, (not(equals(Xcoord, 1));not(equals(Ycoord, 1));not(equals(Time, 0)))),
 1000          (not(holds_at(location(g1, x, Xcoord, Ycoord), Time));Xcoord=5, Ycoord=1, Time=4, equal(x, y))).
 1001 */
 1002
 1003 /*  not({dif(X, 2)}) :-
 1004       ( { dif(X, 4)
 1005         },
 1006         (   not(equals(X, 1))
 1007         ;   not(equals(Equals_Param, 1))
 1008         ;   not(equals(Time4, 0))
 1009         )
 1010       ),
 1011       holds_at(location(g1, x, X, Equals_Param), Time4),
 1012       (   not(equals(X, 5))
 1013       ;   not(equals(Equals_Param, 1))
 1014       ;   not(equals(Time4, 4))
 1015       ;   not(equal(x, y))
 1016       ).
 1017 */
 1018% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:313
 1019axiom(not({dif(X, 2)}),
 1020   
 1021    [ not(equals(X, 5)),
 1022      not(equals(X, 1)),
 1023      { dif(X, 4)
 1024      },
 1025      holds_at(location(g1, x, X, Equals_Param), Time4)
 1026    ]).
 1027axiom(not({dif(X, 2)}),
 1028   
 1029    [ not(equals(Equals_Param, 1)),
 1030      not(equals(X, 1)),
 1031      { dif(X, 4)
 1032      },
 1033      holds_at(location(g1, x, X, Equals_Param), Time4)
 1034    ]).
 1035axiom(not({dif(X, 2)}),
 1036   
 1037    [ not(equals(Time4, 4)),
 1038      not(equals(X, 1)),
 1039      { dif(X, 4)
 1040      },
 1041      holds_at(location(g1, x, X, Equals_Param), Time4)
 1042    ]).
 1043axiom(not({dif(X, 2)}),
 1044   
 1045    [ not(equal(x, y)),
 1046      not(equals(X, 1)),
 1047      { dif(X, 4)
 1048      },
 1049      holds_at(location(g1, x, X, Equals_Param), Time4)
 1050    ]).
 1051axiom(not({dif(X, 2)}),
 1052   
 1053    [ not(equals(X, 5)),
 1054      not(equals(Equals_Param, 1)),
 1055      { dif(X, 4)
 1056      },
 1057      holds_at(location(g1, x, X, Equals_Param), Time4)
 1058    ]).
 1059axiom(not({dif(X, 2)}),
 1060   
 1061    [ not(equals(Equals_Param, 1)),
 1062      not(equals(Equals_Param, 1)),
 1063      { dif(X, 4)
 1064      },
 1065      holds_at(location(g1, x, X, Equals_Param), Time4)
 1066    ]).
 1067axiom(not({dif(X, 2)}),
 1068   
 1069    [ not(equals(Time4, 4)),
 1070      not(equals(Equals_Param, 1)),
 1071      { dif(X, 4)
 1072      },
 1073      holds_at(location(g1, x, X, Equals_Param), Time4)
 1074    ]).
 1075axiom(not({dif(X, 2)}),
 1076   
 1077    [ not(equal(x, y)),
 1078      not(equals(Equals_Param, 1)),
 1079      { dif(X, 4)
 1080      },
 1081      holds_at(location(g1, x, X, Equals_Param), Time4)
 1082    ]).
 1083axiom(not({dif(X, 2)}),
 1084   
 1085    [ not(equals(X, 5)),
 1086      not(equals(Time4, 0)),
 1087      { dif(X, 4)
 1088      },
 1089      holds_at(location(g1, x, X, Equals_Param), Time4)
 1090    ]).
 1091axiom(not({dif(X, 2)}),
 1092   
 1093    [ not(equals(Equals_Param, 1)),
 1094      not(equals(Time4, 0)),
 1095      { dif(X, 4)
 1096      },
 1097      holds_at(location(g1, x, X, Equals_Param), Time4)
 1098    ]).
 1099axiom(not({dif(X, 2)}),
 1100   
 1101    [ not(equals(Time4, 4)),
 1102      not(equals(Time4, 0)),
 1103      { dif(X, 4)
 1104      },
 1105      holds_at(location(g1, x, X, Equals_Param), Time4)
 1106    ]).
 1107axiom(not({dif(X, 2)}),
 1108   
 1109    [ not(equal(x, y)),
 1110      not(equals(Time4, 0)),
 1111      { dif(X, 4)
 1112      },
 1113      holds_at(location(g1, x, X, Equals_Param), Time4)
 1114    ]).
 1115
 1116 /*  not({dif(X6, 4)}) :-
 1117       (   not(equals(X6, 1))
 1118       ;   not(equals(Equals_Param8, 1))
 1119       ;   not(equals(Time7, 0))
 1120       ),
 1121       { dif(X6, 2)
 1122       },
 1123       holds_at(location(g1, x, X6, Equals_Param8), Time7),
 1124       (   not(equals(X6, 5))
 1125       ;   not(equals(Equals_Param8, 1))
 1126       ;   not(equals(Time7, 4))
 1127       ;   not(equal(x, y))
 1128       ).
 1129 */
 1130axiom(not({dif(X6, 4)}),
 1131   
 1132    [ not(equals(X6, 5)),
 1133      not(equals(X6, 1)),
 1134      { dif(X6, 2)
 1135      },
 1136      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1137    ]).
 1138axiom(not({dif(X6, 4)}),
 1139   
 1140    [ not(equals(Equals_Param8, 1)),
 1141      not(equals(X6, 1)),
 1142      { dif(X6, 2)
 1143      },
 1144      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1145    ]).
 1146axiom(not({dif(X6, 4)}),
 1147   
 1148    [ not(equals(Time7, 4)),
 1149      not(equals(X6, 1)),
 1150      { dif(X6, 2)
 1151      },
 1152      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1153    ]).
 1154axiom(not({dif(X6, 4)}),
 1155   
 1156    [ not(equal(x, y)),
 1157      not(equals(X6, 1)),
 1158      { dif(X6, 2)
 1159      },
 1160      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1161    ]).
 1162axiom(not({dif(X6, 4)}),
 1163   
 1164    [ not(equals(X6, 5)),
 1165      not(equals(Equals_Param8, 1)),
 1166      { dif(X6, 2)
 1167      },
 1168      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1169    ]).
 1170axiom(not({dif(X6, 4)}),
 1171   
 1172    [ not(equals(Equals_Param8, 1)),
 1173      not(equals(Equals_Param8, 1)),
 1174      { dif(X6, 2)
 1175      },
 1176      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1177    ]).
 1178axiom(not({dif(X6, 4)}),
 1179   
 1180    [ not(equals(Time7, 4)),
 1181      not(equals(Equals_Param8, 1)),
 1182      { dif(X6, 2)
 1183      },
 1184      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1185    ]).
 1186axiom(not({dif(X6, 4)}),
 1187   
 1188    [ not(equal(x, y)),
 1189      not(equals(Equals_Param8, 1)),
 1190      { dif(X6, 2)
 1191      },
 1192      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1193    ]).
 1194axiom(not({dif(X6, 4)}),
 1195   
 1196    [ not(equals(X6, 5)),
 1197      not(equals(Time7, 0)),
 1198      { dif(X6, 2)
 1199      },
 1200      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1201    ]).
 1202axiom(not({dif(X6, 4)}),
 1203   
 1204    [ not(equals(Equals_Param8, 1)),
 1205      not(equals(Time7, 0)),
 1206      { dif(X6, 2)
 1207      },
 1208      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1209    ]).
 1210axiom(not({dif(X6, 4)}),
 1211   
 1212    [ not(equals(Time7, 4)),
 1213      not(equals(Time7, 0)),
 1214      { dif(X6, 2)
 1215      },
 1216      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1217    ]).
 1218axiom(not({dif(X6, 4)}),
 1219   
 1220    [ not(equal(x, y)),
 1221      not(equals(Time7, 0)),
 1222      { dif(X6, 2)
 1223      },
 1224      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 1225    ]).
 1226
 1227 /*  equals(X9, 1) :-
 1228       { dif(X9, 4)
 1229       },
 1230       { dif(X9, 2)
 1231       },
 1232       holds_at(location(g1, x, X9, Equals_Param11), Time10),
 1233       (   not(equals(X9, 5))
 1234       ;   not(equals(Equals_Param11, 1))
 1235       ;   not(equals(Time10, 4))
 1236       ;   not(equal(x, y))
 1237       ).
 1238 */
 1239axiom(equals(X9, 1),
 1240   
 1241    [ not(equals(X9, 5)),
 1242      dif(X9, 4),
 1243      dif(X9, 2),
 1244      holds_at(location(g1, x, X9, Equals_Param11), Time10)
 1245    ]).
 1246axiom(equals(X9, 1),
 1247   
 1248    [ not(equals(Equals_Param11, 1)),
 1249      dif(X9, 4),
 1250      dif(X9, 2),
 1251      holds_at(location(g1, x, X9, Equals_Param11), Time10)
 1252    ]).
 1253axiom(equals(X9, 1),
 1254   
 1255    [ not(equals(Time10, 4)),
 1256      dif(X9, 4),
 1257      dif(X9, 2),
 1258      holds_at(location(g1, x, X9, Equals_Param11), Time10)
 1259    ]).
 1260axiom(equals(X9, 1),
 1261   
 1262    [ not(equal(x, y)),
 1263      dif(X9, 4),
 1264      dif(X9, 2),
 1265      holds_at(location(g1, x, X9, Equals_Param11), Time10)
 1266    ]).
 1267
 1268 /*  equals(Equals_Param14, 1) :-
 1269       { dif(X12, 4)
 1270       },
 1271       { dif(X12, 2)
 1272       },
 1273       holds_at(location(g1, x, X12, Equals_Param14), Time13),
 1274       (   not(equals(X12, 5))
 1275       ;   not(equals(Equals_Param14, 1))
 1276       ;   not(equals(Time13, 4))
 1277       ;   not(equal(x, y))
 1278       ).
 1279 */
 1280axiom(equals(Equals_Param14, 1),
 1281   
 1282    [ not(equals(X12, 5)),
 1283      dif(X12, 4),
 1284      dif(X12, 2),
 1285      holds_at(location(g1, x, X12, Equals_Param14), Time13)
 1286    ]).
 1287axiom(equals(Equals_Param14, 1),
 1288   
 1289    [ not(equals(Equals_Param14, 1)),
 1290      dif(X12, 4),
 1291      dif(X12, 2),
 1292      holds_at(location(g1, x, X12, Equals_Param14), Time13)
 1293    ]).
 1294axiom(equals(Equals_Param14, 1),
 1295   
 1296    [ not(equals(Time13, 4)),
 1297      dif(X12, 4),
 1298      dif(X12, 2),
 1299      holds_at(location(g1, x, X12, Equals_Param14), Time13)
 1300    ]).
 1301axiom(equals(Equals_Param14, 1),
 1302   
 1303    [ not(equal(x, y)),
 1304      dif(X12, 4),
 1305      dif(X12, 2),
 1306      holds_at(location(g1, x, X12, Equals_Param14), Time13)
 1307    ]).
 1308
 1309 /*  equals(Time16, 0) :-
 1310       { dif(X15, 4)
 1311       },
 1312       { dif(X15, 2)
 1313       },
 1314       holds_at(location(g1, x, X15, Equals_Param17), Time16),
 1315       (   not(equals(X15, 5))
 1316       ;   not(equals(Equals_Param17, 1))
 1317       ;   not(equals(Time16, 4))
 1318       ;   not(equal(x, y))
 1319       ).
 1320 */
 1321axiom(equals(Time16, 0),
 1322   
 1323    [ not(equals(X15, 5)),
 1324      dif(X15, 4),
 1325      dif(X15, 2),
 1326      holds_at(location(g1, x, X15, Equals_Param17), Time16)
 1327    ]).
 1328axiom(equals(Time16, 0),
 1329   
 1330    [ not(equals(Equals_Param17, 1)),
 1331      dif(X15, 4),
 1332      dif(X15, 2),
 1333      holds_at(location(g1, x, X15, Equals_Param17), Time16)
 1334    ]).
 1335axiom(equals(Time16, 0),
 1336   
 1337    [ not(equals(Time16, 4)),
 1338      dif(X15, 4),
 1339      dif(X15, 2),
 1340      holds_at(location(g1, x, X15, Equals_Param17), Time16)
 1341    ]).
 1342axiom(equals(Time16, 0),
 1343   
 1344    [ not(equal(x, y)),
 1345      dif(X15, 4),
 1346      dif(X15, 2),
 1347      holds_at(location(g1, x, X15, Equals_Param17), Time16)
 1348    ]).
 1349
 1350 /*  not(holds_at(location(g1, x, X18, Equals_Param20), Time19)) :-
 1351       (   not(equals(X18, 5))
 1352       ;   not(equals(Equals_Param20, 1))
 1353       ;   not(equals(Time19, 4))
 1354       ;   not(equal(x, y))
 1355       ),
 1356       { dif(X18, 2)
 1357       },
 1358       { dif(X18, 4)
 1359       },
 1360       (   not(equals(X18, 1))
 1361       ;   not(equals(Equals_Param20, 1))
 1362       ;   not(equals(Time19, 0))
 1363       ).
 1364 */
 1365axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1366   
 1367    [ not(equals(X18, 1)),
 1368      not(equals(X18, 5)),
 1369      dif(X18, 2),
 1370      dif(X18, 4)
 1371    ]).
 1372axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1373   
 1374    [ not(equals(Equals_Param20, 1)),
 1375      not(equals(X18, 5)),
 1376      dif(X18, 2),
 1377      dif(X18, 4)
 1378    ]).
 1379axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1380   
 1381    [ not(equals(Time19, 0)),
 1382      not(equals(X18, 5)),
 1383      dif(X18, 2),
 1384      dif(X18, 4)
 1385    ]).
 1386axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1387   
 1388    [ not(equals(X18, 1)),
 1389      not(equals(Equals_Param20, 1)),
 1390      dif(X18, 2),
 1391      dif(X18, 4)
 1392    ]).
 1393axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1394   
 1395    [ not(equals(Equals_Param20, 1)),
 1396      not(equals(Equals_Param20, 1)),
 1397      dif(X18, 2),
 1398      dif(X18, 4)
 1399    ]).
 1400axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1401   
 1402    [ not(equals(Time19, 0)),
 1403      not(equals(Equals_Param20, 1)),
 1404      dif(X18, 2),
 1405      dif(X18, 4)
 1406    ]).
 1407axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1408   
 1409    [ not(equals(X18, 1)),
 1410      not(equals(Time19, 4)),
 1411      dif(X18, 2),
 1412      dif(X18, 4)
 1413    ]).
 1414axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1415   
 1416    [ not(equals(Equals_Param20, 1)),
 1417      not(equals(Time19, 4)),
 1418      dif(X18, 2),
 1419      dif(X18, 4)
 1420    ]).
 1421axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1422   
 1423    [ not(equals(Time19, 0)),
 1424      not(equals(Time19, 4)),
 1425      dif(X18, 2),
 1426      dif(X18, 4)
 1427    ]).
 1428axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1429   
 1430    [ not(equals(X18, 1)),
 1431      not(equal(x, y)),
 1432      dif(X18, 2),
 1433      dif(X18, 4)
 1434    ]).
 1435axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1436   
 1437    [ not(equals(Equals_Param20, 1)),
 1438      not(equal(x, y)),
 1439      dif(X18, 2),
 1440      dif(X18, 4)
 1441    ]).
 1442axiom(not(holds_at(location(g1, x, X18, Equals_Param20), Time19)),
 1443   
 1444    [ not(equals(Time19, 0)),
 1445      not(equal(x, y)),
 1446      dif(X18, 2),
 1447      dif(X18, 4)
 1448    ]).
 1449
 1450 /*  equals(X21, 5) :-
 1451       holds_at(location(g1, x, X21, Equals_Param23), Time22),
 1452       { dif(X21, 2)
 1453       },
 1454       { dif(X21, 4)
 1455       },
 1456       (   not(equals(X21, 1))
 1457       ;   not(equals(Equals_Param23, 1))
 1458       ;   not(equals(Time22, 0))
 1459       ).
 1460 */
 1461axiom(equals(X21, 5),
 1462   
 1463    [ not(equals(X21, 1)),
 1464      holds_at(location(g1, x, X21, Equals_Param23), Time22),
 1465      dif(X21, 2),
 1466      dif(X21, 4)
 1467    ]).
 1468axiom(equals(X21, 5),
 1469   
 1470    [ not(equals(Equals_Param23, 1)),
 1471      holds_at(location(g1, x, X21, Equals_Param23), Time22),
 1472      dif(X21, 2),
 1473      dif(X21, 4)
 1474    ]).
 1475axiom(equals(X21, 5),
 1476   
 1477    [ not(equals(Time22, 0)),
 1478      holds_at(location(g1, x, X21, Equals_Param23), Time22),
 1479      dif(X21, 2),
 1480      dif(X21, 4)
 1481    ]).
 1482
 1483 /*  equals(Equals_Param26, 1) :-
 1484       holds_at(location(g1, x, X24, Equals_Param26), Time25),
 1485       { dif(X24, 2)
 1486       },
 1487       { dif(X24, 4)
 1488       },
 1489       (   not(equals(X24, 1))
 1490       ;   not(equals(Equals_Param26, 1))
 1491       ;   not(equals(Time25, 0))
 1492       ).
 1493 */
 1494axiom(equals(Equals_Param26, 1),
 1495   
 1496    [ not(equals(X24, 1)),
 1497      holds_at(location(g1, x, X24, Equals_Param26), Time25),
 1498      dif(X24, 2),
 1499      dif(X24, 4)
 1500    ]).
 1501axiom(equals(Equals_Param26, 1),
 1502   
 1503    [ not(equals(Equals_Param26, 1)),
 1504      holds_at(location(g1, x, X24, Equals_Param26), Time25),
 1505      dif(X24, 2),
 1506      dif(X24, 4)
 1507    ]).
 1508axiom(equals(Equals_Param26, 1),
 1509   
 1510    [ not(equals(Time25, 0)),
 1511      holds_at(location(g1, x, X24, Equals_Param26), Time25),
 1512      dif(X24, 2),
 1513      dif(X24, 4)
 1514    ]).
 1515
 1516 /*  equals(Time28, 4) :-
 1517       holds_at(location(g1, x, X27, Equals_Param29), Time28),
 1518       { dif(X27, 2)
 1519       },
 1520       { dif(X27, 4)
 1521       },
 1522       (   not(equals(X27, 1))
 1523       ;   not(equals(Equals_Param29, 1))
 1524       ;   not(equals(Time28, 0))
 1525       ).
 1526 */
 1527axiom(equals(Time28, 4),
 1528   
 1529    [ not(equals(X27, 1)),
 1530      holds_at(location(g1, x, X27, Equals_Param29), Time28),
 1531      dif(X27, 2),
 1532      dif(X27, 4)
 1533    ]).
 1534axiom(equals(Time28, 4),
 1535   
 1536    [ not(equals(Equals_Param29, 1)),
 1537      holds_at(location(g1, x, X27, Equals_Param29), Time28),
 1538      dif(X27, 2),
 1539      dif(X27, 4)
 1540    ]).
 1541axiom(equals(Time28, 4),
 1542   
 1543    [ not(equals(Time28, 0)),
 1544      holds_at(location(g1, x, X27, Equals_Param29), Time28),
 1545      dif(X27, 2),
 1546      dif(X27, 4)
 1547    ]).
 1548
 1549 /*  equal(x, y) :-
 1550       holds_at(location(g1, x, X30, Equals_Param32), Time31),
 1551       { dif(X30, 2)
 1552       },
 1553       { dif(X30, 4)
 1554       },
 1555       (   not(equals(X30, 1))
 1556       ;   not(equals(Equals_Param32, 1))
 1557       ;   not(equals(Time31, 0))
 1558       ).
 1559 */
 1560axiom(equal(x, y),
 1561   
 1562    [ not(equals(X30, 1)),
 1563      holds_at(location(g1, x, X30, Equals_Param32), Time31),
 1564      dif(X30, 2),
 1565      dif(X30, 4)
 1566    ]).
 1567axiom(equal(x, y),
 1568   
 1569    [ not(equals(Equals_Param32, 1)),
 1570      holds_at(location(g1, x, X30, Equals_Param32), Time31),
 1571      dif(X30, 2),
 1572      dif(X30, 4)
 1573    ]).
 1574axiom(equal(x, y),
 1575   
 1576    [ not(equals(Time31, 0)),
 1577      holds_at(location(g1, x, X30, Equals_Param32), Time31),
 1578      dif(X30, 2),
 1579      dif(X30, 4)
 1580    ]).
 1581
 1582
 1583% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:315
 1584% [xcoord,ycoord,time]
 1585% xcoord!=% 2 & xcoord!=4 & !(xcoord=5 & ycoord=1 & time=4) ->
 1586% !HoldsAt(Location(G1,Y,xcoord,ycoord),time) |
 1587% xcoord=1 & ycoord=1 & time=0 & Equal(X,Y).
 1588
 1589 /*   if(({dif(Xcoord, 2)}, {dif(Xcoord, 4)}, (not(equals(Xcoord, 5));not(equals(Ycoord, 1));not(equals(Time, 4)))),
 1590          (not(holds_at(location(g1, y, Xcoord, Ycoord), Time));Xcoord=1, Ycoord=1, Time=0, equal(x, y))).
 1591 */
 1592
 1593 /*  not({dif(Y, 2)}) :-
 1594       ( { dif(Y, 4)
 1595         },
 1596         (   not(equals(Y, 5))
 1597         ;   not(equals(Equals_Param, 1))
 1598         ;   not(equals(Time4, 4))
 1599         )
 1600       ),
 1601       holds_at(location(g1, y, Y, Equals_Param), Time4),
 1602       (   not(equals(Y, 1))
 1603       ;   not(equals(Equals_Param, 1))
 1604       ;   not(equals(Time4, 0))
 1605       ;   not(equal(x, y))
 1606       ).
 1607 */
 1608% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:318
 1609axiom(not({dif(Y, 2)}),
 1610   
 1611    [ not(equals(Y, 1)),
 1612      not(equals(Y, 5)),
 1613      { dif(Y, 4)
 1614      },
 1615      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1616    ]).
 1617axiom(not({dif(Y, 2)}),
 1618   
 1619    [ not(equals(Equals_Param, 1)),
 1620      not(equals(Y, 5)),
 1621      { dif(Y, 4)
 1622      },
 1623      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1624    ]).
 1625axiom(not({dif(Y, 2)}),
 1626   
 1627    [ not(equals(Time4, 0)),
 1628      not(equals(Y, 5)),
 1629      { dif(Y, 4)
 1630      },
 1631      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1632    ]).
 1633axiom(not({dif(Y, 2)}),
 1634   
 1635    [ not(equal(x, y)),
 1636      not(equals(Y, 5)),
 1637      { dif(Y, 4)
 1638      },
 1639      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1640    ]).
 1641axiom(not({dif(Y, 2)}),
 1642   
 1643    [ not(equals(Y, 1)),
 1644      not(equals(Equals_Param, 1)),
 1645      { dif(Y, 4)
 1646      },
 1647      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1648    ]).
 1649axiom(not({dif(Y, 2)}),
 1650   
 1651    [ not(equals(Equals_Param, 1)),
 1652      not(equals(Equals_Param, 1)),
 1653      { dif(Y, 4)
 1654      },
 1655      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1656    ]).
 1657axiom(not({dif(Y, 2)}),
 1658   
 1659    [ not(equals(Time4, 0)),
 1660      not(equals(Equals_Param, 1)),
 1661      { dif(Y, 4)
 1662      },
 1663      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1664    ]).
 1665axiom(not({dif(Y, 2)}),
 1666   
 1667    [ not(equal(x, y)),
 1668      not(equals(Equals_Param, 1)),
 1669      { dif(Y, 4)
 1670      },
 1671      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1672    ]).
 1673axiom(not({dif(Y, 2)}),
 1674   
 1675    [ not(equals(Y, 1)),
 1676      not(equals(Time4, 4)),
 1677      { dif(Y, 4)
 1678      },
 1679      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1680    ]).
 1681axiom(not({dif(Y, 2)}),
 1682   
 1683    [ not(equals(Equals_Param, 1)),
 1684      not(equals(Time4, 4)),
 1685      { dif(Y, 4)
 1686      },
 1687      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1688    ]).
 1689axiom(not({dif(Y, 2)}),
 1690   
 1691    [ not(equals(Time4, 0)),
 1692      not(equals(Time4, 4)),
 1693      { dif(Y, 4)
 1694      },
 1695      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1696    ]).
 1697axiom(not({dif(Y, 2)}),
 1698   
 1699    [ not(equal(x, y)),
 1700      not(equals(Time4, 4)),
 1701      { dif(Y, 4)
 1702      },
 1703      holds_at(location(g1, y, Y, Equals_Param), Time4)
 1704    ]).
 1705
 1706 /*  not({dif(Y6, 4)}) :-
 1707       (   not(equals(Y6, 5))
 1708       ;   not(equals(Equals_Param8, 1))
 1709       ;   not(equals(Time7, 4))
 1710       ),
 1711       { dif(Y6, 2)
 1712       },
 1713       holds_at(location(g1, y, Y6, Equals_Param8), Time7),
 1714       (   not(equals(Y6, 1))
 1715       ;   not(equals(Equals_Param8, 1))
 1716       ;   not(equals(Time7, 0))
 1717       ;   not(equal(x, y))
 1718       ).
 1719 */
 1720axiom(not({dif(Y6, 4)}),
 1721   
 1722    [ not(equals(Y6, 1)),
 1723      not(equals(Y6, 5)),
 1724      { dif(Y6, 2)
 1725      },
 1726      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1727    ]).
 1728axiom(not({dif(Y6, 4)}),
 1729   
 1730    [ not(equals(Equals_Param8, 1)),
 1731      not(equals(Y6, 5)),
 1732      { dif(Y6, 2)
 1733      },
 1734      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1735    ]).
 1736axiom(not({dif(Y6, 4)}),
 1737   
 1738    [ not(equals(Time7, 0)),
 1739      not(equals(Y6, 5)),
 1740      { dif(Y6, 2)
 1741      },
 1742      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1743    ]).
 1744axiom(not({dif(Y6, 4)}),
 1745   
 1746    [ not(equal(x, y)),
 1747      not(equals(Y6, 5)),
 1748      { dif(Y6, 2)
 1749      },
 1750      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1751    ]).
 1752axiom(not({dif(Y6, 4)}),
 1753   
 1754    [ not(equals(Y6, 1)),
 1755      not(equals(Equals_Param8, 1)),
 1756      { dif(Y6, 2)
 1757      },
 1758      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1759    ]).
 1760axiom(not({dif(Y6, 4)}),
 1761   
 1762    [ not(equals(Equals_Param8, 1)),
 1763      not(equals(Equals_Param8, 1)),
 1764      { dif(Y6, 2)
 1765      },
 1766      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1767    ]).
 1768axiom(not({dif(Y6, 4)}),
 1769   
 1770    [ not(equals(Time7, 0)),
 1771      not(equals(Equals_Param8, 1)),
 1772      { dif(Y6, 2)
 1773      },
 1774      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1775    ]).
 1776axiom(not({dif(Y6, 4)}),
 1777   
 1778    [ not(equal(x, y)),
 1779      not(equals(Equals_Param8, 1)),
 1780      { dif(Y6, 2)
 1781      },
 1782      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1783    ]).
 1784axiom(not({dif(Y6, 4)}),
 1785   
 1786    [ not(equals(Y6, 1)),
 1787      not(equals(Time7, 4)),
 1788      { dif(Y6, 2)
 1789      },
 1790      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1791    ]).
 1792axiom(not({dif(Y6, 4)}),
 1793   
 1794    [ not(equals(Equals_Param8, 1)),
 1795      not(equals(Time7, 4)),
 1796      { dif(Y6, 2)
 1797      },
 1798      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1799    ]).
 1800axiom(not({dif(Y6, 4)}),
 1801   
 1802    [ not(equals(Time7, 0)),
 1803      not(equals(Time7, 4)),
 1804      { dif(Y6, 2)
 1805      },
 1806      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1807    ]).
 1808axiom(not({dif(Y6, 4)}),
 1809   
 1810    [ not(equal(x, y)),
 1811      not(equals(Time7, 4)),
 1812      { dif(Y6, 2)
 1813      },
 1814      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 1815    ]).
 1816
 1817 /*  equals(Y9, 5) :-
 1818       { dif(Y9, 4)
 1819       },
 1820       { dif(Y9, 2)
 1821       },
 1822       holds_at(location(g1, y, Y9, Equals_Param11), Time10),
 1823       (   not(equals(Y9, 1))
 1824       ;   not(equals(Equals_Param11, 1))
 1825       ;   not(equals(Time10, 0))
 1826       ;   not(equal(x, y))
 1827       ).
 1828 */
 1829axiom(equals(Y9, 5),
 1830   
 1831    [ not(equals(Y9, 1)),
 1832      dif(Y9, 4),
 1833      dif(Y9, 2),
 1834      holds_at(location(g1, y, Y9, Equals_Param11), Time10)
 1835    ]).
 1836axiom(equals(Y9, 5),
 1837   
 1838    [ not(equals(Equals_Param11, 1)),
 1839      dif(Y9, 4),
 1840      dif(Y9, 2),
 1841      holds_at(location(g1, y, Y9, Equals_Param11), Time10)
 1842    ]).
 1843axiom(equals(Y9, 5),
 1844   
 1845    [ not(equals(Time10, 0)),
 1846      dif(Y9, 4),
 1847      dif(Y9, 2),
 1848      holds_at(location(g1, y, Y9, Equals_Param11), Time10)
 1849    ]).
 1850axiom(equals(Y9, 5),
 1851   
 1852    [ not(equal(x, y)),
 1853      dif(Y9, 4),
 1854      dif(Y9, 2),
 1855      holds_at(location(g1, y, Y9, Equals_Param11), Time10)
 1856    ]).
 1857
 1858 /*  equals(Equals_Param14, 1) :-
 1859       { dif(Y12, 4)
 1860       },
 1861       { dif(Y12, 2)
 1862       },
 1863       holds_at(location(g1, y, Y12, Equals_Param14), Time13),
 1864       (   not(equals(Y12, 1))
 1865       ;   not(equals(Equals_Param14, 1))
 1866       ;   not(equals(Time13, 0))
 1867       ;   not(equal(x, y))
 1868       ).
 1869 */
 1870axiom(equals(Equals_Param14, 1),
 1871   
 1872    [ not(equals(Y12, 1)),
 1873      dif(Y12, 4),
 1874      dif(Y12, 2),
 1875      holds_at(location(g1, y, Y12, Equals_Param14), Time13)
 1876    ]).
 1877axiom(equals(Equals_Param14, 1),
 1878   
 1879    [ not(equals(Equals_Param14, 1)),
 1880      dif(Y12, 4),
 1881      dif(Y12, 2),
 1882      holds_at(location(g1, y, Y12, Equals_Param14), Time13)
 1883    ]).
 1884axiom(equals(Equals_Param14, 1),
 1885   
 1886    [ not(equals(Time13, 0)),
 1887      dif(Y12, 4),
 1888      dif(Y12, 2),
 1889      holds_at(location(g1, y, Y12, Equals_Param14), Time13)
 1890    ]).
 1891axiom(equals(Equals_Param14, 1),
 1892   
 1893    [ not(equal(x, y)),
 1894      dif(Y12, 4),
 1895      dif(Y12, 2),
 1896      holds_at(location(g1, y, Y12, Equals_Param14), Time13)
 1897    ]).
 1898
 1899 /*  equals(Time16, 4) :-
 1900       { dif(Y15, 4)
 1901       },
 1902       { dif(Y15, 2)
 1903       },
 1904       holds_at(location(g1, y, Y15, Equals_Param17), Time16),
 1905       (   not(equals(Y15, 1))
 1906       ;   not(equals(Equals_Param17, 1))
 1907       ;   not(equals(Time16, 0))
 1908       ;   not(equal(x, y))
 1909       ).
 1910 */
 1911axiom(equals(Time16, 4),
 1912   
 1913    [ not(equals(Y15, 1)),
 1914      dif(Y15, 4),
 1915      dif(Y15, 2),
 1916      holds_at(location(g1, y, Y15, Equals_Param17), Time16)
 1917    ]).
 1918axiom(equals(Time16, 4),
 1919   
 1920    [ not(equals(Equals_Param17, 1)),
 1921      dif(Y15, 4),
 1922      dif(Y15, 2),
 1923      holds_at(location(g1, y, Y15, Equals_Param17), Time16)
 1924    ]).
 1925axiom(equals(Time16, 4),
 1926   
 1927    [ not(equals(Time16, 0)),
 1928      dif(Y15, 4),
 1929      dif(Y15, 2),
 1930      holds_at(location(g1, y, Y15, Equals_Param17), Time16)
 1931    ]).
 1932axiom(equals(Time16, 4),
 1933   
 1934    [ not(equal(x, y)),
 1935      dif(Y15, 4),
 1936      dif(Y15, 2),
 1937      holds_at(location(g1, y, Y15, Equals_Param17), Time16)
 1938    ]).
 1939
 1940 /*  not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)) :-
 1941       (   not(equals(Y18, 1))
 1942       ;   not(equals(Equals_Param20, 1))
 1943       ;   not(equals(Time19, 0))
 1944       ;   not(equal(x, y))
 1945       ),
 1946       { dif(Y18, 2)
 1947       },
 1948       { dif(Y18, 4)
 1949       },
 1950       (   not(equals(Y18, 5))
 1951       ;   not(equals(Equals_Param20, 1))
 1952       ;   not(equals(Time19, 4))
 1953       ).
 1954 */
 1955axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 1956   
 1957    [ not(equals(Y18, 5)),
 1958      not(equals(Y18, 1)),
 1959      dif(Y18, 2),
 1960      dif(Y18, 4)
 1961    ]).
 1962axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 1963   
 1964    [ not(equals(Equals_Param20, 1)),
 1965      not(equals(Y18, 1)),
 1966      dif(Y18, 2),
 1967      dif(Y18, 4)
 1968    ]).
 1969axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 1970   
 1971    [ not(equals(Time19, 4)),
 1972      not(equals(Y18, 1)),
 1973      dif(Y18, 2),
 1974      dif(Y18, 4)
 1975    ]).
 1976axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 1977   
 1978    [ not(equals(Y18, 5)),
 1979      not(equals(Equals_Param20, 1)),
 1980      dif(Y18, 2),
 1981      dif(Y18, 4)
 1982    ]).
 1983axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 1984   
 1985    [ not(equals(Equals_Param20, 1)),
 1986      not(equals(Equals_Param20, 1)),
 1987      dif(Y18, 2),
 1988      dif(Y18, 4)
 1989    ]).
 1990axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 1991   
 1992    [ not(equals(Time19, 4)),
 1993      not(equals(Equals_Param20, 1)),
 1994      dif(Y18, 2),
 1995      dif(Y18, 4)
 1996    ]).
 1997axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 1998   
 1999    [ not(equals(Y18, 5)),
 2000      not(equals(Time19, 0)),
 2001      dif(Y18, 2),
 2002      dif(Y18, 4)
 2003    ]).
 2004axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 2005   
 2006    [ not(equals(Equals_Param20, 1)),
 2007      not(equals(Time19, 0)),
 2008      dif(Y18, 2),
 2009      dif(Y18, 4)
 2010    ]).
 2011axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 2012   
 2013    [ not(equals(Time19, 4)),
 2014      not(equals(Time19, 0)),
 2015      dif(Y18, 2),
 2016      dif(Y18, 4)
 2017    ]).
 2018axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 2019   
 2020    [ not(equals(Y18, 5)),
 2021      not(equal(x, y)),
 2022      dif(Y18, 2),
 2023      dif(Y18, 4)
 2024    ]).
 2025axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 2026   
 2027    [ not(equals(Equals_Param20, 1)),
 2028      not(equal(x, y)),
 2029      dif(Y18, 2),
 2030      dif(Y18, 4)
 2031    ]).
 2032axiom(not(holds_at(location(g1, y, Y18, Equals_Param20), Time19)),
 2033   
 2034    [ not(equals(Time19, 4)),
 2035      not(equal(x, y)),
 2036      dif(Y18, 2),
 2037      dif(Y18, 4)
 2038    ]).
 2039
 2040 /*  equals(Y21, 1) :-
 2041       holds_at(location(g1, y, Y21, Equals_Param23), Time22),
 2042       { dif(Y21, 2)
 2043       },
 2044       { dif(Y21, 4)
 2045       },
 2046       (   not(equals(Y21, 5))
 2047       ;   not(equals(Equals_Param23, 1))
 2048       ;   not(equals(Time22, 4))
 2049       ).
 2050 */
 2051axiom(equals(Y21, 1),
 2052   
 2053    [ not(equals(Y21, 5)),
 2054      holds_at(location(g1, y, Y21, Equals_Param23), Time22),
 2055      dif(Y21, 2),
 2056      dif(Y21, 4)
 2057    ]).
 2058axiom(equals(Y21, 1),
 2059   
 2060    [ not(equals(Equals_Param23, 1)),
 2061      holds_at(location(g1, y, Y21, Equals_Param23), Time22),
 2062      dif(Y21, 2),
 2063      dif(Y21, 4)
 2064    ]).
 2065axiom(equals(Y21, 1),
 2066   
 2067    [ not(equals(Time22, 4)),
 2068      holds_at(location(g1, y, Y21, Equals_Param23), Time22),
 2069      dif(Y21, 2),
 2070      dif(Y21, 4)
 2071    ]).
 2072
 2073 /*  equals(Equals_Param26, 1) :-
 2074       holds_at(location(g1, y, Y24, Equals_Param26), Time25),
 2075       { dif(Y24, 2)
 2076       },
 2077       { dif(Y24, 4)
 2078       },
 2079       (   not(equals(Y24, 5))
 2080       ;   not(equals(Equals_Param26, 1))
 2081       ;   not(equals(Time25, 4))
 2082       ).
 2083 */
 2084axiom(equals(Equals_Param26, 1),
 2085   
 2086    [ not(equals(Y24, 5)),
 2087      holds_at(location(g1, y, Y24, Equals_Param26), Time25),
 2088      dif(Y24, 2),
 2089      dif(Y24, 4)
 2090    ]).
 2091axiom(equals(Equals_Param26, 1),
 2092   
 2093    [ not(equals(Equals_Param26, 1)),
 2094      holds_at(location(g1, y, Y24, Equals_Param26), Time25),
 2095      dif(Y24, 2),
 2096      dif(Y24, 4)
 2097    ]).
 2098axiom(equals(Equals_Param26, 1),
 2099   
 2100    [ not(equals(Time25, 4)),
 2101      holds_at(location(g1, y, Y24, Equals_Param26), Time25),
 2102      dif(Y24, 2),
 2103      dif(Y24, 4)
 2104    ]).
 2105
 2106 /*  equals(Time28, 0) :-
 2107       holds_at(location(g1, y, Y27, Equals_Param29), Time28),
 2108       { dif(Y27, 2)
 2109       },
 2110       { dif(Y27, 4)
 2111       },
 2112       (   not(equals(Y27, 5))
 2113       ;   not(equals(Equals_Param29, 1))
 2114       ;   not(equals(Time28, 4))
 2115       ).
 2116 */
 2117axiom(equals(Time28, 0),
 2118   
 2119    [ not(equals(Y27, 5)),
 2120      holds_at(location(g1, y, Y27, Equals_Param29), Time28),
 2121      dif(Y27, 2),
 2122      dif(Y27, 4)
 2123    ]).
 2124axiom(equals(Time28, 0),
 2125   
 2126    [ not(equals(Equals_Param29, 1)),
 2127      holds_at(location(g1, y, Y27, Equals_Param29), Time28),
 2128      dif(Y27, 2),
 2129      dif(Y27, 4)
 2130    ]).
 2131axiom(equals(Time28, 0),
 2132   
 2133    [ not(equals(Time28, 4)),
 2134      holds_at(location(g1, y, Y27, Equals_Param29), Time28),
 2135      dif(Y27, 2),
 2136      dif(Y27, 4)
 2137    ]).
 2138
 2139 /*  equal(x, y) :-
 2140       holds_at(location(g1, y, Y30, Equals_Param32), Time31),
 2141       { dif(Y30, 2)
 2142       },
 2143       { dif(Y30, 4)
 2144       },
 2145       (   not(equals(Y30, 5))
 2146       ;   not(equals(Equals_Param32, 1))
 2147       ;   not(equals(Time31, 4))
 2148       ).
 2149 */
 2150axiom(equal(x, y),
 2151   
 2152    [ not(equals(Y30, 5)),
 2153      holds_at(location(g1, y, Y30, Equals_Param32), Time31),
 2154      dif(Y30, 2),
 2155      dif(Y30, 4)
 2156    ]).
 2157axiom(equal(x, y),
 2158   
 2159    [ not(equals(Equals_Param32, 1)),
 2160      holds_at(location(g1, y, Y30, Equals_Param32), Time31),
 2161      dif(Y30, 2),
 2162      dif(Y30, 4)
 2163    ]).
 2164axiom(equal(x, y),
 2165   
 2166    [ not(equals(Time31, 4)),
 2167      holds_at(location(g1, y, Y30, Equals_Param32), Time31),
 2168      dif(Y30, 2),
 2169      dif(Y30, 4)
 2170    ]).
 2171
 2172% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:320
 2173% range time 0 4
 2174% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:321
 2175==> range(time,0,4).
 2176
 2177% range xcoord 0 5
 2178% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:322
 2179==> range(xcoord,0,5).
 2180
 2181% range ycoord 0 1
 2182% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:323
 2183==> range(ycoord,0,1).
 2184
 2185% range offset 0 0
 2186% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:324
 2187==> range(offset,0,0).
 2188%; End of file.
 2189%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 2190%; FILE: examples/Cassimatis2002/OneScreen.e
 2191%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 2192%;
 2193%; Copyright (c) 2005 IBM Corporation and others.
 2194%; All rights reserved. This program and the accompanying materials
 2195%; are made available under the terms of the Common Public License v1.0
 2196%; which accompanies this distribution, and is available at
 2197%; http://www.eclipse.org/legal/cpl-v10.html
 2198%;
 2199%; Contributors:
 2200%; IBM - Initial implementation
 2201%;
 2202%; @phdthesis{Cassimatis:2002,
 2203%;   author = "Nicholas L. Cassimatis",
 2204%;   year = "2002",
 2205%;   title = "Polyscheme: A Cognitive Architecture for Integrating Multiple Representation and Inference Schemes",
 2206%;   address = "Cambridge, MA",
 2207%;   school = "Program in Media Arts and Sciences, School of Architecture and Planning, Massachusetts Institute of Technology",
 2208%; }
 2209%;
 2210
 2211% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:351
 2212% load foundations/Root.e
 2213
 2214% load foundations/EC.e
 2215
 2216% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:353
 2217% load examples/Cassimatis2002/PolySpace.e
 2218
 2219% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:355
 2220% grid G1
 2221% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:356
 2222==> t(grid,g1).
 2223
 2224% object X,Y,Screen
 2225% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:357
 2226==> t(object,x).
 2227==> t(object,y).
 2228==> t(object,screen).
 2229%; perceptions:
 2230
 2231
 2232% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:359
 2233% Shape(X,Round).
 2234shape(x,round).
 2235
 2236
 2237% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:360
 2238% Color(X,Red).
 2239color(x,red).
 2240
 2241
 2242% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:361
 2243% Shape(Y,Round).
 2244shape(y,round).
 2245
 2246
 2247% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:362
 2248% Color(Y,Red).
 2249color(y,red).
 2250
 2251
 2252% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:363
 2253% Shape(Screen,Square).
 2254shape(screen,square).
 2255
 2256
 2257% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:364
 2258% Color(Screen,Green).
 2259color(screen,green).
 2260
 2261
 2262% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:365
 2263% [time]
 2264 % HoldsAt(Location(G1,Screen,2,0),time).
 2265holds_at(location(g1,screen,2,0),Time).
 2266
 2267
 2268% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:366
 2269% HoldsAt(Location(G1,X,1,1),0).
 2270axiom(initially(location(g1, x, 1, 1)),
 2271    []).
 2272
 2273
 2274% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:367
 2275% HoldsAt(Location(G1,Y,3,1),2).
 2276holds_at(location(g1,y,3,1),2).
 2277
 2278
 2279% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:369
 2280% [xcoord,ycoord,time]
 2281% xcoord!=% 2 & !(xcoord=1 & ycoord=1 & time=0) ->
 2282% !HoldsAt(Location(G1,X,xcoord,ycoord),time) |
 2283% xcoord=3 & ycoord=1 & time=2 & Equal(X,Y).
 2284
 2285 /*   if(({dif(Xcoord, 2)}, (not(equals(Xcoord, 1));not(equals(Ycoord, 1));not(equals(Time, 0)))),
 2286          (not(holds_at(location(g1, x, Xcoord, Ycoord), Time));Xcoord=3, Ycoord=1, Time=2, equal(x, y))).
 2287 */
 2288
 2289 /*  not({dif(X, 2)}) :-
 2290       (   not(equals(X, 1))
 2291       ;   not(equals(Equals_Param, 1))
 2292       ;   not(equals(Time4, 0))
 2293       ),
 2294       holds_at(location(g1, x, X, Equals_Param), Time4),
 2295       (   not(equals(X, 3))
 2296       ;   not(equals(Equals_Param, 1))
 2297       ;   not(equals(Time4, 2))
 2298       ;   not(equal(x, y))
 2299       ).
 2300 */
 2301% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:372
 2302axiom(not({dif(X, 2)}),
 2303   
 2304    [ not(equals(X, 3)),
 2305      not(equals(X, 1)),
 2306      holds_at(location(g1, x, X, Equals_Param), Time4)
 2307    ]).
 2308axiom(not({dif(X, 2)}),
 2309   
 2310    [ not(equals(Equals_Param, 1)),
 2311      not(equals(X, 1)),
 2312      holds_at(location(g1, x, X, Equals_Param), Time4)
 2313    ]).
 2314axiom(not({dif(X, 2)}),
 2315   
 2316    [ not(equals(Time4, 2)),
 2317      not(equals(X, 1)),
 2318      holds_at(location(g1, x, X, Equals_Param), Time4)
 2319    ]).
 2320axiom(not({dif(X, 2)}),
 2321   
 2322    [ not(equal(x, y)),
 2323      not(equals(X, 1)),
 2324      holds_at(location(g1, x, X, Equals_Param), Time4)
 2325    ]).
 2326axiom(not({dif(X, 2)}),
 2327   
 2328    [ not(equals(X, 3)),
 2329      not(equals(Equals_Param, 1)),
 2330      holds_at(location(g1, x, X, Equals_Param), Time4)
 2331    ]).
 2332axiom(not({dif(X, 2)}),
 2333   
 2334    [ not(equals(Equals_Param, 1)),
 2335      not(equals(Equals_Param, 1)),
 2336      holds_at(location(g1, x, X, Equals_Param), Time4)
 2337    ]).
 2338axiom(not({dif(X, 2)}),
 2339   
 2340    [ not(equals(Time4, 2)),
 2341      not(equals(Equals_Param, 1)),
 2342      holds_at(location(g1, x, X, Equals_Param), Time4)
 2343    ]).
 2344axiom(not({dif(X, 2)}),
 2345   
 2346    [ not(equal(x, y)),
 2347      not(equals(Equals_Param, 1)),
 2348      holds_at(location(g1, x, X, Equals_Param), Time4)
 2349    ]).
 2350axiom(not({dif(X, 2)}),
 2351   
 2352    [ not(equals(X, 3)),
 2353      not(equals(Time4, 0)),
 2354      holds_at(location(g1, x, X, Equals_Param), Time4)
 2355    ]).
 2356axiom(not({dif(X, 2)}),
 2357   
 2358    [ not(equals(Equals_Param, 1)),
 2359      not(equals(Time4, 0)),
 2360      holds_at(location(g1, x, X, Equals_Param), Time4)
 2361    ]).
 2362axiom(not({dif(X, 2)}),
 2363   
 2364    [ not(equals(Time4, 2)),
 2365      not(equals(Time4, 0)),
 2366      holds_at(location(g1, x, X, Equals_Param), Time4)
 2367    ]).
 2368axiom(not({dif(X, 2)}),
 2369   
 2370    [ not(equal(x, y)),
 2371      not(equals(Time4, 0)),
 2372      holds_at(location(g1, x, X, Equals_Param), Time4)
 2373    ]).
 2374
 2375 /*  equals(X6, 1) :-
 2376       { dif(X6, 2)
 2377       },
 2378       holds_at(location(g1, x, X6, Equals_Param8), Time7),
 2379       (   not(equals(X6, 3))
 2380       ;   not(equals(Equals_Param8, 1))
 2381       ;   not(equals(Time7, 2))
 2382       ;   not(equal(x, y))
 2383       ).
 2384 */
 2385axiom(equals(X6, 1),
 2386   
 2387    [ not(equals(X6, 3)),
 2388      dif(X6, 2),
 2389      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 2390    ]).
 2391axiom(equals(X6, 1),
 2392   
 2393    [ not(equals(Equals_Param8, 1)),
 2394      dif(X6, 2),
 2395      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 2396    ]).
 2397axiom(equals(X6, 1),
 2398   
 2399    [ not(equals(Time7, 2)),
 2400      dif(X6, 2),
 2401      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 2402    ]).
 2403axiom(equals(X6, 1),
 2404   
 2405    [ not(equal(x, y)),
 2406      dif(X6, 2),
 2407      holds_at(location(g1, x, X6, Equals_Param8), Time7)
 2408    ]).
 2409
 2410 /*  equals(Equals_Param11, 1) :-
 2411       { dif(X9, 2)
 2412       },
 2413       holds_at(location(g1, x, X9, Equals_Param11), Time10),
 2414       (   not(equals(X9, 3))
 2415       ;   not(equals(Equals_Param11, 1))
 2416       ;   not(equals(Time10, 2))
 2417       ;   not(equal(x, y))
 2418       ).
 2419 */
 2420axiom(equals(Equals_Param11, 1),
 2421   
 2422    [ not(equals(X9, 3)),
 2423      dif(X9, 2),
 2424      holds_at(location(g1, x, X9, Equals_Param11), Time10)
 2425    ]).
 2426axiom(equals(Equals_Param11, 1),
 2427   
 2428    [ not(equals(Equals_Param11, 1)),
 2429      dif(X9, 2),
 2430      holds_at(location(g1, x, X9, Equals_Param11), Time10)
 2431    ]).
 2432axiom(equals(Equals_Param11, 1),
 2433   
 2434    [ not(equals(Time10, 2)),
 2435      dif(X9, 2),
 2436      holds_at(location(g1, x, X9, Equals_Param11), Time10)
 2437    ]).
 2438axiom(equals(Equals_Param11, 1),
 2439   
 2440    [ not(equal(x, y)),
 2441      dif(X9, 2),
 2442      holds_at(location(g1, x, X9, Equals_Param11), Time10)
 2443    ]).
 2444
 2445 /*  equals(Time13, 0) :-
 2446       { dif(X12, 2)
 2447       },
 2448       holds_at(location(g1, x, X12, Equals_Param14), Time13),
 2449       (   not(equals(X12, 3))
 2450       ;   not(equals(Equals_Param14, 1))
 2451       ;   not(equals(Time13, 2))
 2452       ;   not(equal(x, y))
 2453       ).
 2454 */
 2455axiom(equals(Time13, 0),
 2456   
 2457    [ not(equals(X12, 3)),
 2458      dif(X12, 2),
 2459      holds_at(location(g1, x, X12, Equals_Param14), Time13)
 2460    ]).
 2461axiom(equals(Time13, 0),
 2462   
 2463    [ not(equals(Equals_Param14, 1)),
 2464      dif(X12, 2),
 2465      holds_at(location(g1, x, X12, Equals_Param14), Time13)
 2466    ]).
 2467axiom(equals(Time13, 0),
 2468   
 2469    [ not(equals(Time13, 2)),
 2470      dif(X12, 2),
 2471      holds_at(location(g1, x, X12, Equals_Param14), Time13)
 2472    ]).
 2473axiom(equals(Time13, 0),
 2474   
 2475    [ not(equal(x, y)),
 2476      dif(X12, 2),
 2477      holds_at(location(g1, x, X12, Equals_Param14), Time13)
 2478    ]).
 2479
 2480 /*  not(holds_at(location(g1, x, X15, Equals_Param17), Time16)) :-
 2481       (   not(equals(X15, 3))
 2482       ;   not(equals(Equals_Param17, 1))
 2483       ;   not(equals(Time16, 2))
 2484       ;   not(equal(x, y))
 2485       ),
 2486       { dif(X15, 2)
 2487       },
 2488       (   not(equals(X15, 1))
 2489       ;   not(equals(Equals_Param17, 1))
 2490       ;   not(equals(Time16, 0))
 2491       ).
 2492 */
 2493axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2494    [not(equals(X15, 1)), not(equals(X15, 3)), dif(X15, 2)]).
 2495axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2496   
 2497    [ not(equals(Equals_Param17, 1)),
 2498      not(equals(X15, 3)),
 2499      dif(X15, 2)
 2500    ]).
 2501axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2502    [not(equals(Time16, 0)), not(equals(X15, 3)), dif(X15, 2)]).
 2503axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2504   
 2505    [ not(equals(X15, 1)),
 2506      not(equals(Equals_Param17, 1)),
 2507      dif(X15, 2)
 2508    ]).
 2509axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2510   
 2511    [ not(equals(Equals_Param17, 1)),
 2512      not(equals(Equals_Param17, 1)),
 2513      dif(X15, 2)
 2514    ]).
 2515axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2516   
 2517    [ not(equals(Time16, 0)),
 2518      not(equals(Equals_Param17, 1)),
 2519      dif(X15, 2)
 2520    ]).
 2521axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2522    [not(equals(X15, 1)), not(equals(Time16, 2)), dif(X15, 2)]).
 2523axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2524   
 2525    [ not(equals(Equals_Param17, 1)),
 2526      not(equals(Time16, 2)),
 2527      dif(X15, 2)
 2528    ]).
 2529axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2530    [not(equals(Time16, 0)), not(equals(Time16, 2)), dif(X15, 2)]).
 2531axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2532    [not(equals(X15, 1)), not(equal(x, y)), dif(X15, 2)]).
 2533axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2534    [not(equals(Equals_Param17, 1)), not(equal(x, y)), dif(X15, 2)]).
 2535axiom(not(holds_at(location(g1, x, X15, Equals_Param17), Time16)),
 2536    [not(equals(Time16, 0)), not(equal(x, y)), dif(X15, 2)]).
 2537
 2538 /*  equals(X18, 3) :-
 2539       holds_at(location(g1, x, X18, Equals_Param20), Time19),
 2540       { dif(X18, 2)
 2541       },
 2542       (   not(equals(X18, 1))
 2543       ;   not(equals(Equals_Param20, 1))
 2544       ;   not(equals(Time19, 0))
 2545       ).
 2546 */
 2547axiom(equals(X18, 3),
 2548   
 2549    [ not(equals(X18, 1)),
 2550      holds_at(location(g1, x, X18, Equals_Param20), Time19),
 2551      dif(X18, 2)
 2552    ]).
 2553axiom(equals(X18, 3),
 2554   
 2555    [ not(equals(Equals_Param20, 1)),
 2556      holds_at(location(g1, x, X18, Equals_Param20), Time19),
 2557      dif(X18, 2)
 2558    ]).
 2559axiom(equals(X18, 3),
 2560   
 2561    [ not(equals(Time19, 0)),
 2562      holds_at(location(g1, x, X18, Equals_Param20), Time19),
 2563      dif(X18, 2)
 2564    ]).
 2565
 2566 /*  equals(Equals_Param23, 1) :-
 2567       holds_at(location(g1, x, X21, Equals_Param23), Time22),
 2568       { dif(X21, 2)
 2569       },
 2570       (   not(equals(X21, 1))
 2571       ;   not(equals(Equals_Param23, 1))
 2572       ;   not(equals(Time22, 0))
 2573       ).
 2574 */
 2575axiom(equals(Equals_Param23, 1),
 2576   
 2577    [ not(equals(X21, 1)),
 2578      holds_at(location(g1, x, X21, Equals_Param23), Time22),
 2579      dif(X21, 2)
 2580    ]).
 2581axiom(equals(Equals_Param23, 1),
 2582   
 2583    [ not(equals(Equals_Param23, 1)),
 2584      holds_at(location(g1, x, X21, Equals_Param23), Time22),
 2585      dif(X21, 2)
 2586    ]).
 2587axiom(equals(Equals_Param23, 1),
 2588   
 2589    [ not(equals(Time22, 0)),
 2590      holds_at(location(g1, x, X21, Equals_Param23), Time22),
 2591      dif(X21, 2)
 2592    ]).
 2593
 2594 /*  equals(Time25, 2) :-
 2595       holds_at(location(g1, x, X24, Equals_Param26), Time25),
 2596       { dif(X24, 2)
 2597       },
 2598       (   not(equals(X24, 1))
 2599       ;   not(equals(Equals_Param26, 1))
 2600       ;   not(equals(Time25, 0))
 2601       ).
 2602 */
 2603axiom(equals(Time25, 2),
 2604   
 2605    [ not(equals(X24, 1)),
 2606      holds_at(location(g1, x, X24, Equals_Param26), Time25),
 2607      dif(X24, 2)
 2608    ]).
 2609axiom(equals(Time25, 2),
 2610   
 2611    [ not(equals(Equals_Param26, 1)),
 2612      holds_at(location(g1, x, X24, Equals_Param26), Time25),
 2613      dif(X24, 2)
 2614    ]).
 2615axiom(equals(Time25, 2),
 2616   
 2617    [ not(equals(Time25, 0)),
 2618      holds_at(location(g1, x, X24, Equals_Param26), Time25),
 2619      dif(X24, 2)
 2620    ]).
 2621
 2622 /*  equal(x, y) :-
 2623       holds_at(location(g1, x, X27, Equals_Param29), Time28),
 2624       { dif(X27, 2)
 2625       },
 2626       (   not(equals(X27, 1))
 2627       ;   not(equals(Equals_Param29, 1))
 2628       ;   not(equals(Time28, 0))
 2629       ).
 2630 */
 2631axiom(equal(x, y),
 2632   
 2633    [ not(equals(X27, 1)),
 2634      holds_at(location(g1, x, X27, Equals_Param29), Time28),
 2635      dif(X27, 2)
 2636    ]).
 2637axiom(equal(x, y),
 2638   
 2639    [ not(equals(Equals_Param29, 1)),
 2640      holds_at(location(g1, x, X27, Equals_Param29), Time28),
 2641      dif(X27, 2)
 2642    ]).
 2643axiom(equal(x, y),
 2644   
 2645    [ not(equals(Time28, 0)),
 2646      holds_at(location(g1, x, X27, Equals_Param29), Time28),
 2647      dif(X27, 2)
 2648    ]).
 2649
 2650
 2651% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:374
 2652% [xcoord,ycoord,time]
 2653% xcoord!=% 2 & !(xcoord=3 & ycoord=1 & time=2) ->
 2654% !HoldsAt(Location(G1,Y,xcoord,ycoord),time) |
 2655% xcoord=1 & ycoord=1 & time=0 & Equal(X,Y).
 2656
 2657 /*   if(({dif(Xcoord, 2)}, (not(equals(Xcoord, 3));not(equals(Ycoord, 1));not(equals(Time, 2)))),
 2658          (not(holds_at(location(g1, y, Xcoord, Ycoord), Time));Xcoord=1, Ycoord=1, Time=0, equal(x, y))).
 2659 */
 2660
 2661 /*  not({dif(Y, 2)}) :-
 2662       (   not(equals(Y, 3))
 2663       ;   not(equals(Equals_Param, 1))
 2664       ;   not(equals(Time4, 2))
 2665       ),
 2666       holds_at(location(g1, y, Y, Equals_Param), Time4),
 2667       (   not(equals(Y, 1))
 2668       ;   not(equals(Equals_Param, 1))
 2669       ;   not(equals(Time4, 0))
 2670       ;   not(equal(x, y))
 2671       ).
 2672 */
 2673% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:377
 2674axiom(not({dif(Y, 2)}),
 2675   
 2676    [ not(equals(Y, 1)),
 2677      not(equals(Y, 3)),
 2678      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2679    ]).
 2680axiom(not({dif(Y, 2)}),
 2681   
 2682    [ not(equals(Equals_Param, 1)),
 2683      not(equals(Y, 3)),
 2684      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2685    ]).
 2686axiom(not({dif(Y, 2)}),
 2687   
 2688    [ not(equals(Time4, 0)),
 2689      not(equals(Y, 3)),
 2690      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2691    ]).
 2692axiom(not({dif(Y, 2)}),
 2693   
 2694    [ not(equal(x, y)),
 2695      not(equals(Y, 3)),
 2696      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2697    ]).
 2698axiom(not({dif(Y, 2)}),
 2699   
 2700    [ not(equals(Y, 1)),
 2701      not(equals(Equals_Param, 1)),
 2702      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2703    ]).
 2704axiom(not({dif(Y, 2)}),
 2705   
 2706    [ not(equals(Equals_Param, 1)),
 2707      not(equals(Equals_Param, 1)),
 2708      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2709    ]).
 2710axiom(not({dif(Y, 2)}),
 2711   
 2712    [ not(equals(Time4, 0)),
 2713      not(equals(Equals_Param, 1)),
 2714      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2715    ]).
 2716axiom(not({dif(Y, 2)}),
 2717   
 2718    [ not(equal(x, y)),
 2719      not(equals(Equals_Param, 1)),
 2720      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2721    ]).
 2722axiom(not({dif(Y, 2)}),
 2723   
 2724    [ not(equals(Y, 1)),
 2725      not(equals(Time4, 2)),
 2726      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2727    ]).
 2728axiom(not({dif(Y, 2)}),
 2729   
 2730    [ not(equals(Equals_Param, 1)),
 2731      not(equals(Time4, 2)),
 2732      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2733    ]).
 2734axiom(not({dif(Y, 2)}),
 2735   
 2736    [ not(equals(Time4, 0)),
 2737      not(equals(Time4, 2)),
 2738      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2739    ]).
 2740axiom(not({dif(Y, 2)}),
 2741   
 2742    [ not(equal(x, y)),
 2743      not(equals(Time4, 2)),
 2744      holds_at(location(g1, y, Y, Equals_Param), Time4)
 2745    ]).
 2746
 2747 /*  equals(Y6, 3) :-
 2748       { dif(Y6, 2)
 2749       },
 2750       holds_at(location(g1, y, Y6, Equals_Param8), Time7),
 2751       (   not(equals(Y6, 1))
 2752       ;   not(equals(Equals_Param8, 1))
 2753       ;   not(equals(Time7, 0))
 2754       ;   not(equal(x, y))
 2755       ).
 2756 */
 2757axiom(equals(Y6, 3),
 2758   
 2759    [ not(equals(Y6, 1)),
 2760      dif(Y6, 2),
 2761      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 2762    ]).
 2763axiom(equals(Y6, 3),
 2764   
 2765    [ not(equals(Equals_Param8, 1)),
 2766      dif(Y6, 2),
 2767      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 2768    ]).
 2769axiom(equals(Y6, 3),
 2770   
 2771    [ not(equals(Time7, 0)),
 2772      dif(Y6, 2),
 2773      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 2774    ]).
 2775axiom(equals(Y6, 3),
 2776   
 2777    [ not(equal(x, y)),
 2778      dif(Y6, 2),
 2779      holds_at(location(g1, y, Y6, Equals_Param8), Time7)
 2780    ]).
 2781
 2782 /*  equals(Equals_Param11, 1) :-
 2783       { dif(Y9, 2)
 2784       },
 2785       holds_at(location(g1, y, Y9, Equals_Param11), Time10),
 2786       (   not(equals(Y9, 1))
 2787       ;   not(equals(Equals_Param11, 1))
 2788       ;   not(equals(Time10, 0))
 2789       ;   not(equal(x, y))
 2790       ).
 2791 */
 2792axiom(equals(Equals_Param11, 1),
 2793   
 2794    [ not(equals(Y9, 1)),
 2795      dif(Y9, 2),
 2796      holds_at(location(g1, y, Y9, Equals_Param11), Time10)
 2797    ]).
 2798axiom(equals(Equals_Param11, 1),
 2799   
 2800    [ not(equals(Equals_Param11, 1)),
 2801      dif(Y9, 2),
 2802      holds_at(location(g1, y, Y9, Equals_Param11), Time10)
 2803    ]).
 2804axiom(equals(Equals_Param11, 1),
 2805   
 2806    [ not(equals(Time10, 0)),
 2807      dif(Y9, 2),
 2808      holds_at(location(g1, y, Y9, Equals_Param11), Time10)
 2809    ]).
 2810axiom(equals(Equals_Param11, 1),
 2811   
 2812    [ not(equal(x, y)),
 2813      dif(Y9, 2),
 2814      holds_at(location(g1, y, Y9, Equals_Param11), Time10)
 2815    ]).
 2816
 2817 /*  equals(Time13, 2) :-
 2818       { dif(Y12, 2)
 2819       },
 2820       holds_at(location(g1, y, Y12, Equals_Param14), Time13),
 2821       (   not(equals(Y12, 1))
 2822       ;   not(equals(Equals_Param14, 1))
 2823       ;   not(equals(Time13, 0))
 2824       ;   not(equal(x, y))
 2825       ).
 2826 */
 2827axiom(equals(Time13, 2),
 2828   
 2829    [ not(equals(Y12, 1)),
 2830      dif(Y12, 2),
 2831      holds_at(location(g1, y, Y12, Equals_Param14), Time13)
 2832    ]).
 2833axiom(equals(Time13, 2),
 2834   
 2835    [ not(equals(Equals_Param14, 1)),
 2836      dif(Y12, 2),
 2837      holds_at(location(g1, y, Y12, Equals_Param14), Time13)
 2838    ]).
 2839axiom(equals(Time13, 2),
 2840   
 2841    [ not(equals(Time13, 0)),
 2842      dif(Y12, 2),
 2843      holds_at(location(g1, y, Y12, Equals_Param14), Time13)
 2844    ]).
 2845axiom(equals(Time13, 2),
 2846   
 2847    [ not(equal(x, y)),
 2848      dif(Y12, 2),
 2849      holds_at(location(g1, y, Y12, Equals_Param14), Time13)
 2850    ]).
 2851
 2852 /*  not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)) :-
 2853       (   not(equals(Y15, 1))
 2854       ;   not(equals(Equals_Param17, 1))
 2855       ;   not(equals(Time16, 0))
 2856       ;   not(equal(x, y))
 2857       ),
 2858       { dif(Y15, 2)
 2859       },
 2860       (   not(equals(Y15, 3))
 2861       ;   not(equals(Equals_Param17, 1))
 2862       ;   not(equals(Time16, 2))
 2863       ).
 2864 */
 2865axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2866    [not(equals(Y15, 3)), not(equals(Y15, 1)), dif(Y15, 2)]).
 2867axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2868   
 2869    [ not(equals(Equals_Param17, 1)),
 2870      not(equals(Y15, 1)),
 2871      dif(Y15, 2)
 2872    ]).
 2873axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2874    [not(equals(Time16, 2)), not(equals(Y15, 1)), dif(Y15, 2)]).
 2875axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2876   
 2877    [ not(equals(Y15, 3)),
 2878      not(equals(Equals_Param17, 1)),
 2879      dif(Y15, 2)
 2880    ]).
 2881axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2882   
 2883    [ not(equals(Equals_Param17, 1)),
 2884      not(equals(Equals_Param17, 1)),
 2885      dif(Y15, 2)
 2886    ]).
 2887axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2888   
 2889    [ not(equals(Time16, 2)),
 2890      not(equals(Equals_Param17, 1)),
 2891      dif(Y15, 2)
 2892    ]).
 2893axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2894    [not(equals(Y15, 3)), not(equals(Time16, 0)), dif(Y15, 2)]).
 2895axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2896   
 2897    [ not(equals(Equals_Param17, 1)),
 2898      not(equals(Time16, 0)),
 2899      dif(Y15, 2)
 2900    ]).
 2901axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2902    [not(equals(Time16, 2)), not(equals(Time16, 0)), dif(Y15, 2)]).
 2903axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2904    [not(equals(Y15, 3)), not(equal(x, y)), dif(Y15, 2)]).
 2905axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2906    [not(equals(Equals_Param17, 1)), not(equal(x, y)), dif(Y15, 2)]).
 2907axiom(not(holds_at(location(g1, y, Y15, Equals_Param17), Time16)),
 2908    [not(equals(Time16, 2)), not(equal(x, y)), dif(Y15, 2)]).
 2909
 2910 /*  equals(Y18, 1) :-
 2911       holds_at(location(g1, y, Y18, Equals_Param20), Time19),
 2912       { dif(Y18, 2)
 2913       },
 2914       (   not(equals(Y18, 3))
 2915       ;   not(equals(Equals_Param20, 1))
 2916       ;   not(equals(Time19, 2))
 2917       ).
 2918 */
 2919axiom(equals(Y18, 1),
 2920   
 2921    [ not(equals(Y18, 3)),
 2922      holds_at(location(g1, y, Y18, Equals_Param20), Time19),
 2923      dif(Y18, 2)
 2924    ]).
 2925axiom(equals(Y18, 1),
 2926   
 2927    [ not(equals(Equals_Param20, 1)),
 2928      holds_at(location(g1, y, Y18, Equals_Param20), Time19),
 2929      dif(Y18, 2)
 2930    ]).
 2931axiom(equals(Y18, 1),
 2932   
 2933    [ not(equals(Time19, 2)),
 2934      holds_at(location(g1, y, Y18, Equals_Param20), Time19),
 2935      dif(Y18, 2)
 2936    ]).
 2937
 2938 /*  equals(Equals_Param23, 1) :-
 2939       holds_at(location(g1, y, Y21, Equals_Param23), Time22),
 2940       { dif(Y21, 2)
 2941       },
 2942       (   not(equals(Y21, 3))
 2943       ;   not(equals(Equals_Param23, 1))
 2944       ;   not(equals(Time22, 2))
 2945       ).
 2946 */
 2947axiom(equals(Equals_Param23, 1),
 2948   
 2949    [ not(equals(Y21, 3)),
 2950      holds_at(location(g1, y, Y21, Equals_Param23), Time22),
 2951      dif(Y21, 2)
 2952    ]).
 2953axiom(equals(Equals_Param23, 1),
 2954   
 2955    [ not(equals(Equals_Param23, 1)),
 2956      holds_at(location(g1, y, Y21, Equals_Param23), Time22),
 2957      dif(Y21, 2)
 2958    ]).
 2959axiom(equals(Equals_Param23, 1),
 2960   
 2961    [ not(equals(Time22, 2)),
 2962      holds_at(location(g1, y, Y21, Equals_Param23), Time22),
 2963      dif(Y21, 2)
 2964    ]).
 2965
 2966 /*  equals(Time25, 0) :-
 2967       holds_at(location(g1, y, Y24, Equals_Param26), Time25),
 2968       { dif(Y24, 2)
 2969       },
 2970       (   not(equals(Y24, 3))
 2971       ;   not(equals(Equals_Param26, 1))
 2972       ;   not(equals(Time25, 2))
 2973       ).
 2974 */
 2975axiom(equals(Time25, 0),
 2976   
 2977    [ not(equals(Y24, 3)),
 2978      holds_at(location(g1, y, Y24, Equals_Param26), Time25),
 2979      dif(Y24, 2)
 2980    ]).
 2981axiom(equals(Time25, 0),
 2982   
 2983    [ not(equals(Equals_Param26, 1)),
 2984      holds_at(location(g1, y, Y24, Equals_Param26), Time25),
 2985      dif(Y24, 2)
 2986    ]).
 2987axiom(equals(Time25, 0),
 2988   
 2989    [ not(equals(Time25, 2)),
 2990      holds_at(location(g1, y, Y24, Equals_Param26), Time25),
 2991      dif(Y24, 2)
 2992    ]).
 2993
 2994 /*  equal(x, y) :-
 2995       holds_at(location(g1, y, Y27, Equals_Param29), Time28),
 2996       { dif(Y27, 2)
 2997       },
 2998       (   not(equals(Y27, 3))
 2999       ;   not(equals(Equals_Param29, 1))
 3000       ;   not(equals(Time28, 2))
 3001       ).
 3002 */
 3003axiom(equal(x, y),
 3004   
 3005    [ not(equals(Y27, 3)),
 3006      holds_at(location(g1, y, Y27, Equals_Param29), Time28),
 3007      dif(Y27, 2)
 3008    ]).
 3009axiom(equal(x, y),
 3010   
 3011    [ not(equals(Equals_Param29, 1)),
 3012      holds_at(location(g1, y, Y27, Equals_Param29), Time28),
 3013      dif(Y27, 2)
 3014    ]).
 3015axiom(equal(x, y),
 3016   
 3017    [ not(equals(Time28, 2)),
 3018      holds_at(location(g1, y, Y27, Equals_Param29), Time28),
 3019      dif(Y27, 2)
 3020    ]).
 3021
 3022% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:379
 3023% range time 0 2
 3024% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:380
 3025==> range(time,0,2).
 3026
 3027% range xcoord 0 4
 3028% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:381
 3029==> range(xcoord,0,4).
 3030
 3031% range ycoord 0 2
 3032% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:382
 3033==> range(ycoord,0,2).
 3034
 3035% range offset 0 0
 3036% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:383
 3037==> range(offset,0,0).
 3038%; End of file.
 3039%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3040%; FILE: examples/BrewkaDixKonolige1997/Wine.e
 3041%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3042%;
 3043%; Copyright (c) 2005 IBM Corporation and others.
 3044%; All rights reserved. This program and the accompanying materials
 3045%; are made available under the terms of the Common Public License v1.0
 3046%; which accompanies this distribution, and is available at
 3047%; http://www.eclipse.org/legal/cpl-v10.html
 3048%;
 3049%; Contributors:
 3050%; IBM - Initial implementation
 3051%;
 3052%; reasoning by cases
 3053%; \fullciteA[p. 45]{BrewkaDixKonolige:1997}
 3054%;
 3055%; @book{BrewkaDixKonolige:1997,
 3056%;   author = "Gerhard Brewka and J{\"{u}}rgen Dix and Kurt Konolige",
 3057%;   year = "1997",
 3058%;   title = "Nonmonotonic Reasoning: An Overview",
 3059%;   address = "Stanford, CA",
 3060%;   publisher = "CSLI",
 3061%; }
 3062%;
 3063
 3064% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:413
 3065% load foundations/Root.e
 3066
 3067% load foundations/EC.e
 3068
 3069% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:416
 3070% sort x
 3071% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:417
 3072==> sort(x).
 3073
 3074% x Person
 3075% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:418
 3076==> t(x,person).
 3077
 3078% predicate LikesWine(x)
 3079 %  predicate(likesWine(x)).
 3080% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:420
 3081==> mpred_prop(likesWine(x),predicate).
 3082==> meta_argtypes(likesWine(x)).
 3083
 3084% predicate Italian(x)
 3085 %  predicate(italian(x)).
 3086% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:421
 3087==> mpred_prop(italian(x),predicate).
 3088==> meta_argtypes(italian(x)).
 3089
 3090% predicate French(x)
 3091 %  predicate(french(x)).
 3092% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:422
 3093==> mpred_prop(french(x),predicate).
 3094==> meta_argtypes(french(x)).
 3095
 3096% predicate Ab1(x)
 3097 %  predicate(ab1(x)).
 3098% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:423
 3099==> mpred_prop(ab1(x),predicate).
 3100==> meta_argtypes(ab1(x)).
 3101
 3102% predicate Ab2(x)
 3103 %  predicate(ab2(x)).
 3104% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:424
 3105==> mpred_prop(ab2(x),predicate).
 3106==> meta_argtypes(ab2(x)).
 3107
 3108
 3109% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:425
 3110% [x]
 3111 % Italian(x) & !Ab1(x) -> LikesWine(x).
 3112axiom(likesWine(X),
 3113    [italian(X), not(ab1(X))]).
 3114
 3115
 3116% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:426
 3117% [x]
 3118 % French(x) & !Ab2(x) -> LikesWine(x).
 3119axiom(likesWine(X),
 3120    [french(X), not(ab2(X))]).
 3121
 3122
 3123% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:427
 3124% [x]
 3125 % Italian(x) -> !French(x).
 3126axiom(not(french(X)),
 3127    [italian(X)]).
 3128
 3129
 3130% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:429
 3131% Italian(Person) | French(Person).
 3132
 3133 /*   (   italian(person)
 3134      ;   french(person)
 3135      ).
 3136 */
 3137
 3138 /*  italian(person) :-
 3139       not(french(person)).
 3140 */
 3141axiom(italian(person),
 3142    [not(french(person))]).
 3143
 3144 /*  french(person) :-
 3145       not(italian(person)).
 3146 */
 3147axiom(french(person),
 3148    [not(italian(person))]).
 3149
 3150% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:431
 3151% range time 0 0
 3152% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:432
 3153==> range(time,0,0).
 3154
 3155% range offset 1 1
 3156% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:433
 3157==> range(offset,1,1).
 3158
 3159% completion Theta Ab1
 3160% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:435
 3161==> completion(theta).
 3162==> completion(ab1).
 3163
 3164% completion Theta Ab2
 3165% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:436
 3166==> completion(theta).
 3167==> completion(ab2).
 3168%; End of file.
 3169%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3170%; FILE: examples/Shanahan1997/Yale.e
 3171%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3172%;
 3173%; Copyright (c) 2005 IBM Corporation and others.
 3174%; All rights reserved. This program and the accompanying materials
 3175%; are made available under the terms of the Common Public License v1.0
 3176%; which accompanies this distribution, and is available at
 3177%; http://www.eclipse.org/legal/cpl-v10.html
 3178%;
 3179%; Contributors:
 3180%; IBM - Initial implementation
 3181%;
 3182%; @article{HanksMcDermott:1987,
 3183%;   author = "Steve Hanks and Drew V. McDermott",
 3184%;   year = "1987",
 3185%;   title = "Nonmonotonic logic and temporal projection",
 3186%;   journal = "Artificial Intelligence",
 3187%;   volume = "33",
 3188%;   number = "3",
 3189%;   pages = "379--412",
 3190%; }
 3191%;
 3192%; \fullciteA[pp. 322--323]{Shanahan:1997}
 3193%;
 3194%; @book{Shanahan:1997,
 3195%;   author = "Murray Shanahan",
 3196%;   year = "1997",
 3197%;   title = "Solving the Frame Problem",
 3198%;   address = "Cambridge, MA",
 3199%;   publisher = "MIT Press",
 3200%; }
 3201%;
 3202%; deduction
 3203%;
 3204%; modifications from Shanahan's formulation:
 3205%; InitiallyP -> HoldsAt
 3206%; timestamps
 3207%; added [time] Terminates(Shoot(),Loaded(),time).
 3208%;
 3209
 3210% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:482
 3211% option showpred off
 3212% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:483
 3213:- set_ec_option(showpred, off). 3214
 3215% load foundations/Root.e
 3216
 3217% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:485
 3218% load foundations/EC.e
 3219
 3220% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:487
 3221% event Load()
 3222 %  event(load()).
 3223% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:488
 3224==> mpred_prop(load(),event).
 3225==> meta_argtypes(load()).
 3226
 3227% event Shoot()
 3228 %  event(shoot()).
 3229% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:489
 3230==> mpred_prop(shoot(),event).
 3231==> meta_argtypes(shoot()).
 3232
 3233% event Sneeze()
 3234 %  event(sneeze()).
 3235% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:490
 3236==> mpred_prop(sneeze(),event).
 3237==> meta_argtypes(sneeze()).
 3238
 3239% fluent Loaded()
 3240 %  fluent(loaded()).
 3241% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:491
 3242==> mpred_prop(loaded(),fluent).
 3243==> meta_argtypes(loaded()).
 3244
 3245% fluent Alive()
 3246 %  fluent(alive()).
 3247% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:492
 3248==> mpred_prop(alive(),fluent).
 3249==> meta_argtypes(alive()).
 3250
 3251
 3252% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:493
 3253% [time]
 3254 % Initiates(Load(),Loaded(),time).
 3255axiom(initiates(load(), loaded(), Time),
 3256    []).
 3257
 3258
 3259% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:494
 3260% [time]
 3261 % HoldsAt(Loaded(),time) -> Terminates(Shoot(),Alive(),time).
 3262axiom(terminates(shoot(), alive(), Time),
 3263    [holds_at(loaded(), Time)]).
 3264
 3265
 3266% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:495
 3267% [time]
 3268 % Terminates(Shoot(),Loaded(),time).
 3269axiom(terminates(shoot(), loaded(), Time),
 3270    []).
 3271
 3272
 3273% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:497
 3274% HoldsAt(Alive(),0).
 3275axiom(initially(alive()),
 3276    []).
 3277
 3278
 3279% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:498
 3280% !HoldsAt(Loaded(),0).
 3281 %  not(initially(loaded())).
 3282axiom(not(initially(loaded())),
 3283    []).
 3284
 3285
 3286% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:499
 3287% Happens(Load(),0).
 3288axiom(happens(load(), t),
 3289    [is_time(0)]).
 3290
 3291
 3292% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:500
 3293% Happens(Sneeze(),1).
 3294axiom(happens(sneeze(), start),
 3295    [is_time(1), b(t, start), ignore(t+1=start)]).
 3296
 3297
 3298% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:501
 3299% Happens(Shoot(),2).
 3300axiom(happens(shoot(), t2),
 3301    [is_time(2), b(t, t2), ignore(t+2=t2)]).
 3302
 3303% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:503
 3304% completion Happens
 3305% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:504
 3306==> completion(happens).
 3307
 3308% range time 0 3
 3309% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:506
 3310==> range(time,0,3).
 3311
 3312% range offset 1 1
 3313% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:507
 3314==> range(offset,1,1).
 3315%; End of file.
 3316%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3317%; FILE: examples/Shanahan1997/StuffyRoom.e
 3318%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3319%;
 3320%; Copyright (c) 2005 IBM Corporation and others.
 3321%; All rights reserved. This program and the accompanying materials
 3322%; are made available under the terms of the Common Public License v1.0
 3323%; which accompanies this distribution, and is available at
 3324%; http://www.eclipse.org/legal/cpl-v10.html
 3325%;
 3326%; Contributors:
 3327%; IBM - Initial implementation
 3328%;
 3329%; @article{GinsbergSmith:1988a,
 3330%;   author = "Matthew L. Ginsberg and David E. Smith",
 3331%;   year = "1988",
 3332%;   title = "Reasoning about action \uppercase{I}: \uppercase{A} possible worlds approach",
 3333%;   journal = "Artificial Intelligence",
 3334%;   volume = "35",
 3335%;   number = "2",
 3336%;   pages = "165--195",
 3337%; }
 3338%;
 3339%; \fullciteA[pp. 288--289]{Shanahan:1997}
 3340%;
 3341%; @book{Shanahan:1997,
 3342%;   author = "Murray Shanahan",
 3343%;   year = "1997",
 3344%;   title = "Solving the Frame Problem",
 3345%;   address = "Cambridge, MA",
 3346%;   publisher = "MIT Press",
 3347%; }
 3348%;
 3349%; deduction
 3350%;
 3351%; modifications from Shanahan's formulation:
 3352%; timestamps
 3353%; added:
 3354%; !HoldsAt(Blocked1(),0).
 3355%; !HoldsAt(Blocked2(),0).
 3356%;
 3357
 3358% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:554
 3359% load foundations/Root.e
 3360
 3361% load foundations/EC.e
 3362
 3363% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:557
 3364% event Close1()
 3365 %  event(close1()).
 3366% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:558
 3367==> mpred_prop(close1(),event).
 3368==> meta_argtypes(close1()).
 3369
 3370% event Close2()
 3371 %  event(close2()).
 3372% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:559
 3373==> mpred_prop(close2(),event).
 3374==> meta_argtypes(close2()).
 3375
 3376% event Start()
 3377 %  event(start()).
 3378% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:560
 3379==> mpred_prop(start(),event).
 3380==> meta_argtypes(start()).
 3381
 3382% fluent Blocked1()
 3383 %  fluent(blocked1()).
 3384% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:561
 3385==> mpred_prop(blocked1(),fluent).
 3386==> meta_argtypes(blocked1()).
 3387
 3388% fluent Blocked2()
 3389 %  fluent(blocked2()).
 3390% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:562
 3391==> mpred_prop(blocked2(),fluent).
 3392==> meta_argtypes(blocked2()).
 3393
 3394% fluent Stuffy()
 3395 %  fluent(stuffy()).
 3396% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:563
 3397==> mpred_prop(stuffy(),fluent).
 3398==> meta_argtypes(stuffy()).
 3399
 3400% noninertial Stuffy
 3401% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:564
 3402==> noninertial(stuffy).
 3403
 3404
 3405% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:565
 3406% [time]
 3407 % Initiates(Close1(),Blocked1(),time).
 3408axiom(initiates(close1(), blocked1(), Time),
 3409    []).
 3410
 3411
 3412% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:566
 3413% [time]
 3414 % Initiates(Close2(),Blocked2(),time).
 3415axiom(initiates(close2(), blocked2(), Time),
 3416    []).
 3417
 3418
 3419% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:568
 3420% [time]
 3421% HoldsAt(Stuffy(),time) <->
 3422% HoldsAt(Blocked1(),time)&HoldsAt(Blocked2(),time).
 3423
 3424 /*  holds_at(stuffy(), Time) <->
 3425       holds_at(blocked1(), Time),
 3426       holds_at(blocked2(), Time).
 3427 */
 3428% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:570
 3429axiom(holds_at(stuffy(), Time),
 3430    [holds_at(blocked1(), Time), holds_at(blocked2(), Time)]).
 3431
 3432 /*   if(holds_at(stuffy(), Time),
 3433          (holds_at(blocked1(), Time), holds_at(blocked2(), Time))).
 3434 */
 3435
 3436 /*  not(holds_at(stuffy(), Time1)) :-
 3437       (   not(holds_at(blocked1(), Time1))
 3438       ;   not(holds_at(blocked2(), Time1))
 3439       ).
 3440 */
 3441axiom(not(holds_at(stuffy(), Time1)),
 3442    [not(holds_at(blocked1(), Time1))]).
 3443axiom(not(holds_at(stuffy(), Time1)),
 3444    [not(holds_at(blocked2(), Time1))]).
 3445
 3446 /*  holds_at(blocked1(), Time2) :-
 3447       holds_at(stuffy(), Time2).
 3448 */
 3449axiom(holds_at(blocked1(), Time2),
 3450    [holds_at(stuffy(), Time2)]).
 3451
 3452 /*  holds_at(blocked2(), Time3) :-
 3453       holds_at(stuffy(), Time3).
 3454 */
 3455axiom(holds_at(blocked2(), Time3),
 3456    [holds_at(stuffy(), Time3)]).
 3457
 3458
 3459% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:572
 3460% [time]
 3461 % Initiates(Start(),Blocked1(),time).
 3462axiom(initiates(start(), blocked1(), Time),
 3463    []).
 3464
 3465
 3466% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:573
 3467% [time]
 3468 % Terminates(Start(),Blocked2(),time).
 3469axiom(terminates(start(), blocked2(), Time),
 3470    []).
 3471
 3472
 3473% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:575
 3474% !HoldsAt(Blocked1(),0).
 3475 %  not(initially(blocked1())).
 3476axiom(not(initially(blocked1())),
 3477    []).
 3478
 3479
 3480% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:576
 3481% !HoldsAt(Blocked2(),0).
 3482 %  not(initially(blocked2())).
 3483axiom(not(initially(blocked2())),
 3484    []).
 3485
 3486
 3487% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:577
 3488% Happens(Start(),0).
 3489axiom(happens(start(), t),
 3490    [is_time(0)]).
 3491
 3492
 3493% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:578
 3494% Happens(Close2(),1).
 3495axiom(happens(close2(), start),
 3496    [is_time(1), b(t, start), ignore(t+1=start)]).
 3497
 3498% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:580
 3499% completion Happens
 3500% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:581
 3501==> completion(happens).
 3502
 3503% range time 0 2
 3504% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:583
 3505==> range(time,0,2).
 3506
 3507% range offset 1 1
 3508% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:584
 3509==> range(offset,1,1).
 3510%; End of file.
 3511%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3512%; FILE: examples/Shanahan1997/BusRide.e
 3513%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3514%;
 3515%; Copyright (c) 2005 IBM Corporation and others.
 3516%; All rights reserved. This program and the accompanying materials
 3517%; are made available under the terms of the Common Public License v1.0
 3518%; which accompanies this distribution, and is available at
 3519%; http://www.eclipse.org/legal/cpl-v10.html
 3520%;
 3521%; Contributors:
 3522%; IBM - Initial implementation
 3523%;
 3524%; @article{Kartha:1994,
 3525%;   author = "G. Neelakantan Kartha",
 3526%;   year = "1994",
 3527%;   title = "Two counterexamples related to \uppercase{B}aker's approach to the frame problem",
 3528%;   journal = "Artificial Intelligence",
 3529%;   volume = "69",
 3530%;   number = "1--2",
 3531%;   pages = "379--391",
 3532%; }
 3533%;
 3534%; \fullciteA[pp. 359--361]{Shanahan:1997}
 3535%;
 3536%; @book{Shanahan:1997,
 3537%;   author = "Murray Shanahan",
 3538%;   year = "1997",
 3539%;   title = "Solving the Frame Problem",
 3540%;   address = "Cambridge, MA",
 3541%;   publisher = "MIT Press",
 3542%; }
 3543%;
 3544%; modifications from Shanahan's formulation:
 3545%; InitiallyN -> !HoldsAt
 3546%; timestamps
 3547%;
 3548
 3549% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:627
 3550% load foundations/Root.e
 3551
 3552% load foundations/EC.e
 3553
 3554% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:630
 3555% fluent HasTicket()
 3556 %  fluent(hasTicket()).
 3557% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:631
 3558==> mpred_prop(hasTicket(),fluent).
 3559==> meta_argtypes(hasTicket()).
 3560
 3561% fluent OnRed()
 3562 %  fluent(onRed()).
 3563% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:632
 3564==> mpred_prop(onRed(),fluent).
 3565==> meta_argtypes(onRed()).
 3566
 3567% fluent OnYellow()
 3568 %  fluent(onYellow()).
 3569% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:633
 3570==> mpred_prop(onYellow(),fluent).
 3571==> meta_argtypes(onYellow()).
 3572
 3573% event Buy()
 3574 %  event(buy()).
 3575% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:634
 3576==> mpred_prop(buy(),event).
 3577==> meta_argtypes(buy()).
 3578
 3579% event Board()
 3580 %  event(board()).
 3581% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:635
 3582==> mpred_prop(board(),event).
 3583==> meta_argtypes(board()).
 3584
 3585% event BoardRed()
 3586 %  event(boardRed()).
 3587% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:636
 3588==> mpred_prop(boardRed(),event).
 3589==> meta_argtypes(boardRed()).
 3590
 3591% event BoardYellow()
 3592 %  event(boardYellow()).
 3593% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:637
 3594==> mpred_prop(boardYellow(),event).
 3595==> meta_argtypes(boardYellow()).
 3596
 3597
 3598% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:638
 3599% [time]
 3600 % Happens(Board(),time) -> Happens(BoardRed(),time) | Happens(BoardYellow(),time).
 3601
 3602 /*   if(happens(board(), Time),
 3603          (happens(boardRed(), Time);happens(boardYellow(), Time))).
 3604 */
 3605
 3606 /*  happens(boardRed(), Maptime) :-
 3607       not(happens(boardYellow(), Maptime)),
 3608       happens(board(), Maptime).
 3609 */
 3610axiom(happens(boardRed(), Maptime),
 3611    [not(happens(boardYellow(), Maptime)), happens(board(), Maptime)]).
 3612
 3613 /*  happens(boardYellow(), Maptime2) :-
 3614       not(happens(boardRed(), Maptime2)),
 3615       happens(board(), Maptime2).
 3616 */
 3617axiom(happens(boardYellow(), Maptime2),
 3618    [not(happens(boardRed(), Maptime2)), happens(board(), Maptime2)]).
 3619
 3620 /*  not(happens(board(), Maptime3)) :-
 3621       not(happens(boardRed(), Maptime3)),
 3622       not(happens(boardYellow(), Maptime3)).
 3623 */
 3624axiom(not(happens(board(), Maptime3)),
 3625   
 3626    [ not(happens(boardRed(), Maptime3)),
 3627      not(happens(boardYellow(), Maptime3))
 3628    ]).
 3629
 3630
 3631% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:640
 3632% [time]
 3633 % Initiates(Buy(),HasTicket(),time).
 3634axiom(initiates(buy(), hasTicket(), Time),
 3635    []).
 3636
 3637
 3638% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:641
 3639% [time]
 3640 % HoldsAt(HasTicket(),time) -> Initiates(BoardRed(),OnRed(),time).
 3641axiom(initiates(boardRed(), onRed(), Time),
 3642    [holds_at(hasTicket(), Time)]).
 3643
 3644
 3645% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:642
 3646% [time]
 3647 % HoldsAt(HasTicket(),time) -> Initiates(BoardYellow(),OnYellow(),time).
 3648axiom(initiates(boardYellow(), onYellow(), Time),
 3649    [holds_at(hasTicket(), Time)]).
 3650
 3651
 3652% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:644
 3653% [time]
 3654 % !(HoldsAt(OnRed(),time) & HoldsAt(OnYellow(),time)).
 3655
 3656 /*   not(( holds_at(onRed(), Time),
 3657            holds_at(onYellow(), Time)
 3658          )).
 3659 */
 3660
 3661 /*  not(holds_at(onRed(), Time1)) :-
 3662       holds_at(onYellow(), Time1).
 3663 */
 3664axiom(not(holds_at(onRed(), Time1)),
 3665    [holds_at(onYellow(), Time1)]).
 3666
 3667 /*  not(holds_at(onYellow(), Time2)) :-
 3668       holds_at(onRed(), Time2).
 3669 */
 3670axiom(not(holds_at(onYellow(), Time2)),
 3671    [holds_at(onRed(), Time2)]).
 3672
 3673
 3674% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:645
 3675% [time]
 3676 % HoldsAt(OnRed(),time) -> HoldsAt(HasTicket(),time).
 3677axiom(holds_at(hasTicket(), Time),
 3678    [holds_at(onRed(), Time)]).
 3679
 3680
 3681% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:646
 3682% [time]
 3683 % HoldsAt(OnYellow(),time) -> HoldsAt(HasTicket(),time).
 3684axiom(holds_at(hasTicket(), Time),
 3685    [holds_at(onYellow(), Time)]).
 3686
 3687
 3688% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:648
 3689% HoldsAt(OnRed(),2).
 3690holds_at(onRed(),2).
 3691
 3692
 3693% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:650
 3694% !HoldsAt(HasTicket(),0).
 3695 %  not(initially(hasTicket())).
 3696axiom(not(initially(hasTicket())),
 3697    []).
 3698
 3699
 3700% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:651
 3701% Happens(Buy(),0).
 3702axiom(happens(buy(), t),
 3703    [is_time(0)]).
 3704
 3705
 3706% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:652
 3707% Happens(Board(),1).
 3708axiom(happens(board(), start),
 3709    [is_time(1), b(t, start), ignore(t+1=start)]).
 3710
 3711
 3712% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:653
 3713%; ABDUCED Happens(BoardRed(), 1).
 3714
 3715% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:655
 3716% completion Happens
 3717% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:656
 3718==> completion(happens).
 3719
 3720% range time 0 2
 3721% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:658
 3722==> range(time,0,2).
 3723
 3724% range offset 1 1
 3725% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:659
 3726==> range(offset,1,1).
 3727%; End of file.
 3728%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3729%; FILE: examples/Shanahan1997/DeadOrAlive.e
 3730%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3731%;
 3732%; Copyright (c) 2005 IBM Corporation and others.
 3733%; All rights reserved. This program and the accompanying materials
 3734%; are made available under the terms of the Common Public License v1.0
 3735%; which accompanies this distribution, and is available at
 3736%; http://www.eclipse.org/legal/cpl-v10.html
 3737%;
 3738%; Contributors:
 3739%; IBM - Initial implementation
 3740%;
 3741%; \fullciteA[p. 324]{Shanahan:1997}
 3742%;
 3743%; @book{Shanahan:1997,
 3744%;   author = "Murray Shanahan",
 3745%;   year = "1997",
 3746%;   title = "Solving the Frame Problem",
 3747%;   address = "Cambridge, MA",
 3748%;   publisher = "MIT Press",
 3749%; }
 3750%;
 3751%; deduction
 3752%;
 3753%; modifications from Shanahan's formulation:
 3754%; InitiallyP -> HoldsAt
 3755%; timestamps
 3756%; added [time] Terminates(Shoot(),Loaded(),time).
 3757%;
 3758
 3759% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:695
 3760% load foundations/Root.e
 3761
 3762% load foundations/EC.e
 3763
 3764% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:698
 3765% event Load()
 3766 %  event(load()).
 3767% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:699
 3768==> mpred_prop(load(),event).
 3769==> meta_argtypes(load()).
 3770
 3771% event Shoot()
 3772 %  event(shoot()).
 3773% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:700
 3774==> mpred_prop(shoot(),event).
 3775==> meta_argtypes(shoot()).
 3776
 3777% event Sneeze()
 3778 %  event(sneeze()).
 3779% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:701
 3780==> mpred_prop(sneeze(),event).
 3781==> meta_argtypes(sneeze()).
 3782
 3783% fluent Loaded()
 3784 %  fluent(loaded()).
 3785% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:702
 3786==> mpred_prop(loaded(),fluent).
 3787==> meta_argtypes(loaded()).
 3788
 3789% fluent Alive()
 3790 %  fluent(alive()).
 3791% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:703
 3792==> mpred_prop(alive(),fluent).
 3793==> meta_argtypes(alive()).
 3794
 3795% fluent Dead()
 3796 %  fluent(dead()).
 3797% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:704
 3798==> mpred_prop(dead(),fluent).
 3799==> meta_argtypes(dead()).
 3800
 3801% noninertial Dead
 3802% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:705
 3803==> noninertial(dead).
 3804
 3805
 3806% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:706
 3807% [time]
 3808 % Initiates(Load(),Loaded(),time).
 3809axiom(initiates(load(), loaded(), Time),
 3810    []).
 3811
 3812
 3813% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:707
 3814% [time]
 3815 % HoldsAt(Loaded(),time) -> Terminates(Shoot(),Alive(),time).
 3816axiom(terminates(shoot(), alive(), Time),
 3817    [holds_at(loaded(), Time)]).
 3818
 3819
 3820% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:708
 3821% [time]
 3822 % Terminates(Shoot(),Loaded(),time).
 3823axiom(terminates(shoot(), loaded(), Time),
 3824    []).
 3825
 3826
 3827% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:709
 3828% [time]
 3829 % HoldsAt(Dead(),time) <-> !HoldsAt(Alive(),time).
 3830
 3831 /*  holds_at(dead(), Time) <->
 3832       not(holds_at(alive(), Time)).
 3833 */
 3834axiom(holds_at(dead(), Time),
 3835    [not(holds_at(alive(), Time))]).
 3836axiom(not(holds_at(alive(), Time)),
 3837    [holds_at(dead(), Time)]).
 3838
 3839
 3840% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:711
 3841% HoldsAt(Alive(),0).
 3842axiom(initially(alive()),
 3843    []).
 3844
 3845
 3846% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:712
 3847% !HoldsAt(Loaded(),0).
 3848 %  not(initially(loaded())).
 3849axiom(not(initially(loaded())),
 3850    []).
 3851
 3852
 3853% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:713
 3854% Happens(Load(),0).
 3855axiom(happens(load(), t),
 3856    [is_time(0)]).
 3857
 3858
 3859% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:714
 3860% Happens(Sneeze(),1).
 3861axiom(happens(sneeze(), start),
 3862    [is_time(1), b(t, start), ignore(t+1=start)]).
 3863
 3864
 3865% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:715
 3866% Happens(Shoot(),2).
 3867axiom(happens(shoot(), t2),
 3868    [is_time(2), b(t, t2), ignore(t+2=t2)]).
 3869
 3870% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:717
 3871% completion Happens
 3872% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:718
 3873==> completion(happens).
 3874
 3875% range time 0 3
 3876% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:720
 3877==> range(time,0,3).
 3878
 3879% range offset 1 1
 3880% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:721
 3881==> range(offset,1,1).
 3882%; End of file.
 3883%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3884%; FILE: examples/Shanahan1997/Supermarket.e
 3885%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 3886%;
 3887%; Copyright (c) 2005 IBM Corporation and others.
 3888%; All rights reserved. This program and the accompanying materials
 3889%; are made available under the terms of the Common Public License v1.0
 3890%; which accompanies this distribution, and is available at
 3891%; http://www.eclipse.org/legal/cpl-v10.html
 3892%;
 3893%; Contributors:
 3894%; IBM - Initial implementation
 3895%;
 3896%; \fullciteA[pp. 302--304]{Shanahan:1997}
 3897%;
 3898%; @book{Shanahan:1997,
 3899%;   author = "Murray Shanahan",
 3900%;   year = "1997",
 3901%;   title = "Solving the Frame Problem",
 3902%;   address = "Cambridge, MA",
 3903%;   publisher = "MIT Press",
 3904%; }
 3905%;
 3906%; deduction
 3907%;
 3908%; modifications from Shanahan's formulation:
 3909%; reformulated using the method of \fullciteA[pp. 460--461]{MillerShanahan:2002}
 3910%;
 3911%; @incollection{MillerShanahan:2002,
 3912%;   author = "Rob Miller and Murray Shanahan",
 3913%;   year = "2002",
 3914%;   title = "Some alternative formulations of the event calculus",
 3915%;   editor = "Antonis C. Kakas and Fariba Sadri",
 3916%;   booktitle = "Computational Logic: Logic Programming and Beyond: Essays in Honour of \uppercase{R}obert \uppercase{A}. \uppercase{K}owalski, Part \uppercase{II}",
 3917%;   series = "Lecture Notes in Computer Science",
 3918%;   volume = "2408",
 3919%;   pages = "452--490",
 3920%;   address = "Berlin",
 3921%;   publisher = "Springer",
 3922%; }
 3923%;
 3924%; added:
 3925%; !HoldsAt(Forwards(), 0).
 3926%; !HoldsAt(Backwards(), 0).
 3927%; !HoldsAt(Spinning(), 0).
 3928%;
 3929
 3930% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:773
 3931% load foundations/Root.e
 3932
 3933% load foundations/EC.e
 3934
 3935% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:776
 3936% event Push()
 3937 %  event(push()).
 3938% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:777
 3939==> mpred_prop(push(),event).
 3940==> meta_argtypes(push()).
 3941
 3942% event Pull()
 3943 %  event(pull()).
 3944% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:778
 3945==> mpred_prop(pull(),event).
 3946==> meta_argtypes(pull()).
 3947
 3948% fluent Forwards()
 3949 %  fluent(forwards()).
 3950% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:779
 3951==> mpred_prop(forwards(),fluent).
 3952==> meta_argtypes(forwards()).
 3953
 3954% fluent Backwards()
 3955 %  fluent(backwards()).
 3956% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:780
 3957==> mpred_prop(backwards(),fluent).
 3958==> meta_argtypes(backwards()).
 3959
 3960% fluent Spinning()
 3961 %  fluent(spinning()).
 3962% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:781
 3963==> mpred_prop(spinning(),fluent).
 3964==> meta_argtypes(spinning()).
 3965
 3966
 3967% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:782
 3968% [time]
 3969% !Happens(Pull(), time) ->
 3970% Initiates(Push(), Forwards(), time).
 3971% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:784
 3972axiom(initiates(push(), forwards(), Time),
 3973    [not(happens(pull(), Time))]).
 3974
 3975
 3976% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:786
 3977% [time]
 3978% !Happens(Pull(), time) ->
 3979% Terminates(Push(), Backwards(), time).
 3980% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:788
 3981axiom(terminates(push(), backwards(), Time),
 3982    [not(happens(pull(), Time))]).
 3983
 3984
 3985% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:790
 3986% [time]
 3987% !Happens(Push(), time) ->
 3988% Initiates(Pull(), Backwards(), time).
 3989% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:792
 3990axiom(initiates(pull(), backwards(), Time),
 3991    [not(happens(push(), Time))]).
 3992
 3993
 3994% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:794
 3995% [time]
 3996% !Happens(Push(), time) ->
 3997% Terminates(Pull(), Forwards(), time).
 3998% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:796
 3999axiom(terminates(pull(), forwards(), Time),
 4000    [not(happens(push(), Time))]).
 4001
 4002
 4003% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:798
 4004% [time]
 4005% Happens(Push(), time) ->
 4006% Initiates(Pull(), Spinning(), time).
 4007% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:800
 4008axiom(requires(push(), Time),
 4009    [initiates(pull(), spinning(), Time)]).
 4010
 4011
 4012% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:802
 4013% [time]
 4014% Happens(Push(), time) ->
 4015% Terminates(Pull(), Forwards(), time).
 4016% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:804
 4017axiom(requires(push(), Time),
 4018    [terminates(pull(), forwards(), Time)]).
 4019
 4020
 4021% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:806
 4022% [time]
 4023% Happens(Push(), time) ->
 4024% Terminates(Pull(), Backwards(), time).
 4025% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:808
 4026axiom(requires(push(), Time),
 4027    [terminates(pull(), backwards(), Time)]).
 4028
 4029
 4030% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:810
 4031% [time]
 4032% !Happens(Pull(), time) ->
 4033% Terminates(Push(), Spinning(), time).
 4034% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:812
 4035axiom(terminates(push(), spinning(), Time),
 4036    [not(happens(pull(), Time))]).
 4037
 4038
 4039% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:814
 4040% [time]
 4041% !Happens(Push(), time) ->
 4042% Terminates(Pull(), Spinning(), time).
 4043% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:816
 4044axiom(terminates(pull(), spinning(), Time),
 4045    [not(happens(push(), Time))]).
 4046
 4047
 4048% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:818
 4049% !HoldsAt(Forwards(), 0).
 4050 %  not(initially(forwards())).
 4051axiom(not(initially(forwards())),
 4052    []).
 4053
 4054
 4055% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:819
 4056% !HoldsAt(Backwards(), 0).
 4057 %  not(initially(backwards())).
 4058axiom(not(initially(backwards())),
 4059    []).
 4060
 4061
 4062% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:820
 4063% !HoldsAt(Spinning(), 0).
 4064 %  not(initially(spinning())).
 4065axiom(not(initially(spinning())),
 4066    []).
 4067
 4068
 4069% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:822
 4070% Happens(Push(), 5).
 4071axiom(happens(push(), t5),
 4072    [is_time(5), b(t, t5), ignore(t+5=t5)]).
 4073
 4074
 4075% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:823
 4076% Happens(Pull(), 5).
 4077axiom(happens(pull(), t5),
 4078    [is_time(5), b(t, t5), ignore(t+5=t5)]).
 4079
 4080
 4081% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:824
 4082% Happens(Pull(), 10).
 4083axiom(happens(pull(), t10),
 4084    [is_time(10), b(t, t10), ignore(t+10=t10)]).
 4085
 4086
 4087% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:825
 4088% Happens(Push(), 10).
 4089axiom(happens(push(), t10),
 4090    [is_time(10), b(t, t10), ignore(t+10=t10)]).
 4091
 4092% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:827
 4093% completion Happens
 4094% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:828
 4095==> completion(happens).
 4096
 4097% range time 0 12
 4098% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:830
 4099==> range(time,0,12).
 4100
 4101% range offset 1 1
 4102% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:831
 4103==> range(offset,1,1).
 4104%; End of file.
 4105%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4106%; FILE: examples/Shanahan1997/StolenCar.e
 4107%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4108%;
 4109%; Copyright (c) 2005 IBM Corporation and others.
 4110%; All rights reserved. This program and the accompanying materials
 4111%; are made available under the terms of the Common Public License v1.0
 4112%; which accompanies this distribution, and is available at
 4113%; http://www.eclipse.org/legal/cpl-v10.html
 4114%;
 4115%; Contributors:
 4116%; IBM - Initial implementation
 4117%;
 4118%; @inproceedings{Kautz:1986,
 4119%;   author = "Henry A. Kautz",
 4120%;   year = "1986",
 4121%;   title = "The Logic of Persistence",
 4122%;   booktitle = "\uppercase{P}roceedings of the \uppercase{F}ifth \uppercase{N}ational \uppercase{C}onference on \uppercase{A}rtificial \uppercase{I}ntelligence",
 4123%;   pages = "401--405",
 4124%;   address = "Los Altos, CA",
 4125%;   publisher = "Morgan Kaufmann",
 4126%; }
 4127%;
 4128%; \fullciteA[p. 359]{Shanahan:1997}
 4129%;
 4130%; @book{Shanahan:1997,
 4131%;   author = "Murray Shanahan",
 4132%;   year = "1997",
 4133%;   title = "Solving the Frame Problem",
 4134%;   address = "Cambridge, MA",
 4135%;   publisher = "MIT Press",
 4136%; }
 4137%;
 4138%; abduction
 4139%;
 4140%; modifications from Shanahan's formulation:
 4141%; timestamps
 4142%; added !HoldsAt(CarParked(),0).
 4143%;
 4144
 4145% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:876
 4146% load foundations/Root.e
 4147
 4148% load foundations/EC.e
 4149
 4150% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:879
 4151% event Park()
 4152 %  event(park()).
 4153% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:880
 4154==> mpred_prop(park(),event).
 4155==> meta_argtypes(park()).
 4156
 4157% event Steal()
 4158 %  event(steal()).
 4159% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:881
 4160==> mpred_prop(steal(),event).
 4161==> meta_argtypes(steal()).
 4162
 4163% fluent CarParked()
 4164 %  fluent(carParked()).
 4165% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:882
 4166==> mpred_prop(carParked(),fluent).
 4167==> meta_argtypes(carParked()).
 4168
 4169
 4170% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:883
 4171% [time]
 4172 % Initiates(Park(),CarParked(),time).
 4173axiom(initiates(park(), carParked(), Time),
 4174    []).
 4175
 4176
 4177% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:884
 4178% [time]
 4179 % Terminates(Steal(),CarParked(),time).
 4180axiom(terminates(steal(), carParked(), Time),
 4181    []).
 4182
 4183
 4184% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:886
 4185% !HoldsAt(CarParked(),0).
 4186 %  not(initially(carParked())).
 4187axiom(not(initially(carParked())),
 4188    []).
 4189
 4190
 4191% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:887
 4192% Happens(Park(),0).
 4193axiom(happens(park(), t),
 4194    [is_time(0)]).
 4195
 4196
 4197% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:888
 4198%; ABDUCED Happens(Steal(), 1).
 4199
 4200
 4201% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:889
 4202% !HoldsAt(CarParked(),2).
 4203 %  not(holds_at(carParked(),2)).
 4204axiom(not(holds_at(carParked(), t2)),
 4205    [b(t, t2), ignore(t+2=t2)]).
 4206
 4207% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:891
 4208% range time 0 2
 4209% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:892
 4210==> range(time,0,2).
 4211
 4212% range offset 1 1
 4213% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:893
 4214==> range(offset,1,1).
 4215%; End of file.
 4216%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4217%; FILE: examples/MillerShanahan2002/Bowl.e
 4218%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4219%;
 4220%; Copyright (c) 2005 IBM Corporation and others.
 4221%; All rights reserved. This program and the accompanying materials
 4222%; are made available under the terms of the Common Public License v1.0
 4223%; which accompanies this distribution, and is available at
 4224%; http://www.eclipse.org/legal/cpl-v10.html
 4225%;
 4226%; Contributors:
 4227%; IBM - Initial implementation
 4228%;
 4229%; \fullciteA[p. 461]{MillerShanahan:2002}
 4230%;
 4231%; @incollection{MillerShanahan:2002,
 4232%;   author = "Rob Miller and Murray Shanahan",
 4233%;   year = "2002",
 4234%;   title = "Some alternative formulations of the event calculus",
 4235%;   editor = "Antonis C. Kakas and Fariba Sadri",
 4236%;   booktitle = "Computational Logic: Logic Programming and Beyond: Essays in Honour of \uppercase{R}obert \uppercase{A}. \uppercase{K}owalski, Part \uppercase{II}",
 4237%;   series = "Lecture Notes in Computer Science",
 4238%;   volume = "2408",
 4239%;   pages = "452--490",
 4240%;   address = "Berlin",
 4241%;   publisher = "Springer",
 4242%; }
 4243%;
 4244
 4245% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:927
 4246% load foundations/Root.e
 4247
 4248% load foundations/EC.e
 4249
 4250% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:930
 4251% event LiftLeft()
 4252 %  event(liftLeft()).
 4253% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:931
 4254==> mpred_prop(liftLeft(),event).
 4255==> meta_argtypes(liftLeft()).
 4256
 4257% event LiftRight()
 4258 %  event(liftRight()).
 4259% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:932
 4260==> mpred_prop(liftRight(),event).
 4261==> meta_argtypes(liftRight()).
 4262
 4263% fluent Spilt()
 4264 %  fluent(spilt()).
 4265% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:933
 4266==> mpred_prop(spilt(),fluent).
 4267==> meta_argtypes(spilt()).
 4268
 4269% fluent Raised()
 4270 %  fluent(raised()).
 4271% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:934
 4272==> mpred_prop(raised(),fluent).
 4273==> meta_argtypes(raised()).
 4274
 4275
 4276% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:935
 4277% [time]
 4278% !Happens(LiftRight(), time) ->
 4279% Initiates(LiftLeft(), Spilt(), time).
 4280% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:937
 4281axiom(initiates(liftLeft(), spilt(), Time),
 4282    [not(happens(liftRight(), Time))]).
 4283
 4284
 4285% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:939
 4286% [time]
 4287% !Happens(LiftLeft(), time) ->
 4288% Initiates(LiftRight(), Spilt(), time).
 4289% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:941
 4290axiom(initiates(liftRight(), spilt(), Time),
 4291    [not(happens(liftLeft(), Time))]).
 4292
 4293
 4294% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:943
 4295% [time]
 4296% Happens(LiftLeft(), time) ->
 4297% Initiates(LiftRight(), Raised(), time).
 4298% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:945
 4299axiom(requires(liftLeft(), Time),
 4300    [initiates(liftRight(), raised(), Time)]).
 4301
 4302
 4303% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:947
 4304% !HoldsAt(Spilt(), 0).
 4305 %  not(initially(spilt())).
 4306axiom(not(initially(spilt())),
 4307    []).
 4308
 4309
 4310% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:948
 4311% !HoldsAt(Raised(), 0).
 4312 %  not(initially(raised())).
 4313axiom(not(initially(raised())),
 4314    []).
 4315
 4316
 4317% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:949
 4318% Happens(LiftLeft(), 2).
 4319axiom(happens(liftLeft(), t2),
 4320    [is_time(2), b(t, t2), ignore(t+2=t2)]).
 4321
 4322
 4323% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:950
 4324% Happens(LiftRight(), 2).
 4325axiom(happens(liftRight(), t2),
 4326    [is_time(2), b(t, t2), ignore(t+2=t2)]).
 4327
 4328% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:952
 4329% completion Happens
 4330% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:953
 4331==> completion(happens).
 4332
 4333% range time 0 3
 4334% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:955
 4335==> range(time,0,3).
 4336
 4337% range offset 1 1
 4338% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:956
 4339==> range(offset,1,1).
 4340%; End of file.
 4341%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4342%; FILE: examples/ReiterCriscuolo1981/NixonDiamond1.e
 4343%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4344%;
 4345%; Copyright (c) 2005 IBM Corporation and others.
 4346%; All rights reserved. This program and the accompanying materials
 4347%; are made available under the terms of the Common Public License v1.0
 4348%; which accompanies this distribution, and is available at
 4349%; http://www.eclipse.org/legal/cpl-v10.html
 4350%;
 4351%; Contributors:
 4352%; IBM - Initial implementation
 4353%;
 4354%; conflicting defaults: showing that inconsistency results
 4355%; without a cancellation rule
 4356%; \fullciteA[p. 274]{ReiterCriscuolo:1981}
 4357%; \fullciteA[pp. 98--99]{McCarthy:1986}
 4358%;
 4359%; @inproceedings{ReiterCriscuolo:1981,
 4360%;   author = "Raymond Reiter and Giovanni Criscuolo",
 4361%;   year = "1981",
 4362%;   title = "On interacting defaults",
 4363%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventh \uppercase{I}nternational \uppercase{J}oint \uppercase{C}onference on \uppercase{A}rtificial \uppercase{I}ntelligence",
 4364%;   volume = "1",
 4365%;   pages = "270--276",
 4366%;   address = "Los Altos, CA",
 4367%;   publisher = "William Kaufmann",
 4368%; }
 4369%;
 4370%; @article{McCarthy:1986,
 4371%;   author = "John McCarthy",
 4372%;   year = "1986",
 4373%;   title = "Applications of circumscription to formalizing common-sense knowledge",
 4374%;   journal = "Artificial Intelligence",
 4375%;   volume = "28",
 4376%;   pages = "89--116".
 4377%; }
 4378%;
 4379
 4380% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1000
 4381% load foundations/Root.e
 4382
 4383% load foundations/EC.e
 4384
 4385% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1003
 4386% sort x
 4387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1004
 4388==> sort(x).
 4389
 4390% predicate Republican(x)
 4391 %  predicate(republican(x)).
 4392% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1006
 4393==> mpred_prop(republican(x),predicate).
 4394==> meta_argtypes(republican(x)).
 4395
 4396% predicate Quaker(x)
 4397 %  predicate(quaker(x)).
 4398% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1007
 4399==> mpred_prop(quaker(x),predicate).
 4400==> meta_argtypes(quaker(x)).
 4401
 4402% predicate Pacifist(x)
 4403 %  predicate(pacifist(x)).
 4404% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1008
 4405==> mpred_prop(pacifist(x),predicate).
 4406==> meta_argtypes(pacifist(x)).
 4407
 4408% predicate Ab1(x)
 4409 %  predicate(ab1(x)).
 4410% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1009
 4411==> mpred_prop(ab1(x),predicate).
 4412==> meta_argtypes(ab1(x)).
 4413
 4414% predicate Ab2(x)
 4415 %  predicate(ab2(x)).
 4416% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1010
 4417==> mpred_prop(ab2(x),predicate).
 4418==> meta_argtypes(ab2(x)).
 4419
 4420% x John
 4421% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1012
 4422==> t(x,john).
 4423
 4424
 4425% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1013
 4426% Republican(John).
 4427republican(john).
 4428
 4429
 4430% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1014
 4431% Quaker(John).
 4432quaker(john).
 4433
 4434
 4435% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1016
 4436% [x]
 4437 % Republican(x) & !Ab1(x) -> !Pacifist(x).
 4438axiom(not(pacifist(X)),
 4439    [republican(X), not(ab1(X))]).
 4440
 4441
 4442% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1017
 4443% [x]
 4444 % Quaker(x) & !Ab2(x) -> Pacifist(x).
 4445axiom(pacifist(X),
 4446    [quaker(X), not(ab2(X))]).
 4447
 4448% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1019
 4449% range time 0 0
 4450% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1020
 4451==> range(time,0,0).
 4452
 4453% range offset 1 1
 4454% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1021
 4455==> range(offset,1,1).
 4456
 4457% completion Theta Ab1
 4458% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1023
 4459==> completion(theta).
 4460==> completion(ab1).
 4461
 4462% completion Theta Ab2
 4463% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1024
 4464==> completion(theta).
 4465==> completion(ab2).
 4466%; End of file.
 4467%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4468%; FILE: examples/ReiterCriscuolo1981/NixonDiamond2.e
 4469%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4470%;
 4471%; Copyright (c) 2005 IBM Corporation and others.
 4472%; All rights reserved. This program and the accompanying materials
 4473%; are made available under the terms of the Common Public License v1.0
 4474%; which accompanies this distribution, and is available at
 4475%; http://www.eclipse.org/legal/cpl-v10.html
 4476%;
 4477%; Contributors:
 4478%; IBM - Initial implementation
 4479%;
 4480%; conflicting defaults: method (D)
 4481%; \fullciteA[p. 274]{ReiterCriscuolo:1981}
 4482%; \fullciteA[pp. 98--99]{McCarthy:1986}
 4483%; \fullciteA[p. 18]{BrewkaDixKonolige:1997}
 4484%;
 4485%; @inproceedings{ReiterCriscuolo:1981,
 4486%;   author = "Raymond Reiter and Giovanni Criscuolo",
 4487%;   year = "1981",
 4488%;   title = "On interacting defaults",
 4489%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventh \uppercase{I}nternational \uppercase{J}oint \uppercase{C}onference on \uppercase{A}rtificial \uppercase{I}ntelligence",
 4490%;   volume = "1",
 4491%;   pages = "270--276",
 4492%;   address = "Los Altos, CA",
 4493%;   publisher = "William Kaufmann",
 4494%; }
 4495%;
 4496%; @article{McCarthy:1986,
 4497%;   author = "John McCarthy",
 4498%;   year = "1986",
 4499%;   title = "Applications of circumscription to formalizing common-sense knowledge",
 4500%;   journal = "Artificial Intelligence",
 4501%;   volume = "28",
 4502%;   pages = "89--116".
 4503%; }
 4504%;
 4505%; @book{BrewkaDixKonolige:1997,
 4506%;   author = "Gerhard Brewka and J{\"{u}}rgen Dix and Kurt Konolige",
 4507%;   year = "1997",
 4508%;   title = "Nonmonotonic Reasoning: An Overview",
 4509%;   address = "Stanford, CA",
 4510%;   publisher = "CSLI",
 4511%; }
 4512%;
 4513
 4514% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1076
 4515% load foundations/Root.e
 4516
 4517% load foundations/EC.e
 4518
 4519% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1079
 4520% sort x
 4521% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1080
 4522==> sort(x).
 4523
 4524% predicate Republican(x)
 4525 %  predicate(republican(x)).
 4526% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1082
 4527==> mpred_prop(republican(x),predicate).
 4528==> meta_argtypes(republican(x)).
 4529
 4530% predicate Quaker(x)
 4531 %  predicate(quaker(x)).
 4532% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1083
 4533==> mpred_prop(quaker(x),predicate).
 4534==> meta_argtypes(quaker(x)).
 4535
 4536% predicate Pacifist(x)
 4537 %  predicate(pacifist(x)).
 4538% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1084
 4539==> mpred_prop(pacifist(x),predicate).
 4540==> meta_argtypes(pacifist(x)).
 4541
 4542% predicate Ab1(x)
 4543 %  predicate(ab1(x)).
 4544% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1085
 4545==> mpred_prop(ab1(x),predicate).
 4546==> meta_argtypes(ab1(x)).
 4547
 4548% predicate Ab2(x)
 4549 %  predicate(ab2(x)).
 4550% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1086
 4551==> mpred_prop(ab2(x),predicate).
 4552==> meta_argtypes(ab2(x)).
 4553
 4554% x John
 4555% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1088
 4556==> t(x,john).
 4557
 4558
 4559% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1089
 4560% Republican(John).
 4561republican(john).
 4562
 4563
 4564% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1090
 4565% Quaker(John).
 4566quaker(john).
 4567
 4568
 4569% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1092
 4570% [x]
 4571 % Republican(x) & !Ab1(x) -> !Pacifist(x).
 4572axiom(not(pacifist(X)),
 4573    [republican(X), not(ab1(X))]).
 4574
 4575
 4576% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1093
 4577% [x]
 4578 % Quaker(x) & !Ab2(x) -> Pacifist(x).
 4579axiom(pacifist(X),
 4580    [quaker(X), not(ab2(X))]).
 4581
 4582% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1094
 4583% Theta: 
 4584next_axiom_uses(theta).
 4585 
 4586
 4587
 4588% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1094
 4589% [x]
 4590 % Republican(x) -> Ab2(x).
 4591axiom(ab2(X),
 4592    [republican(X)]).
 4593
 4594% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1096
 4595% range time 0 0
 4596% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1097
 4597==> range(time,0,0).
 4598
 4599% range offset 1 1
 4600% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1098
 4601==> range(offset,1,1).
 4602
 4603% completion Theta Ab1
 4604% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1100
 4605==> completion(theta).
 4606==> completion(ab1).
 4607
 4608% completion Theta Ab2
 4609% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1101
 4610==> completion(theta).
 4611==> completion(ab2).
 4612%; End of file.
 4613%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4614%; FILE: examples/Mueller2006/Chapter2/Sleep2.e
 4615%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4616%;
 4617%; Copyright (c) 2005 IBM Corporation and others.
 4618%; All rights reserved. This program and the accompanying materials
 4619%; are made available under the terms of the Common Public License v1.0
 4620%; which accompanies this distribution, and is available at
 4621%; http://www.eclipse.org/legal/cpl-v10.html
 4622%;
 4623%; Contributors:
 4624%; IBM - Initial implementation
 4625%;
 4626%; @book{Mueller:2006,
 4627%;   author = "Erik T. Mueller",
 4628%;   year = "2006",
 4629%;   title = "Commonsense Reasoning",
 4630%;   address = "San Francisco",
 4631%;   publisher = "Morgan Kaufmann/Elsevier",
 4632%; }
 4633%;
 4634
 4635% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1128
 4636% load foundations/Root.e
 4637
 4638% load foundations/EC.e
 4639
 4640% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1131
 4641% sort agent
 4642% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1132
 4643==> sort(agent).
 4644
 4645% agent Nathan
 4646% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1134
 4647==> t(agent,nathan).
 4648
 4649% fluent Awake(agent)
 4650 %  fluent(awake(agent)).
 4651% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1136
 4652==> mpred_prop(awake(agent),fluent).
 4653==> meta_argtypes(awake(agent)).
 4654
 4655% event WakeUp(agent)
 4656 %  event(wakeUp(agent)).
 4657% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1138
 4658==> mpred_prop(wakeUp(agent),event).
 4659==> meta_argtypes(wakeUp(agent)).
 4660
 4661% event FallAsleep(agent)
 4662 %  event(fallAsleep(agent)).
 4663% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1139
 4664==> mpred_prop(fallAsleep(agent),event).
 4665==> meta_argtypes(fallAsleep(agent)).
 4666
 4667
 4668% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1140
 4669%; Sigma
 4670% [agent,time]
 4671 % Initiates(WakeUp(agent),Awake(agent),time).
 4672% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1142
 4673axiom(initiates(wakeUp(Agent), awake(Agent), Time),
 4674    []).
 4675
 4676
 4677% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1143
 4678% [agent,time]
 4679 % Terminates(FallAsleep(agent),Awake(agent),time).
 4680axiom(terminates(fallAsleep(Agent), awake(Agent), Time),
 4681    []).
 4682
 4683
 4684% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1145
 4685%; Gamma
 4686
 4687
 4688% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1147
 4689% !HoldsAt(Awake(Nathan),0).
 4690 %  not(initially(awake(nathan))).
 4691axiom(not(initially(awake(nathan))),
 4692    []).
 4693
 4694
 4695% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1148
 4696% HoldsAt(Awake(Nathan),1).
 4697holds_at(awake(nathan),1).
 4698
 4699
 4700% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1150
 4701%; abduced:
 4702%; Happens(WakeUp(Nathan),0).
 4703
 4704% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1153
 4705% range time 0 1
 4706% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1154
 4707==> range(time,0,1).
 4708
 4709% range offset 1 1
 4710% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1155
 4711==> range(offset,1,1).
 4712%; End of file.
 4713%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4714%; FILE: examples/Mueller2006/Chapter2/Sleep1.e
 4715%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4716%;
 4717%; Copyright (c) 2005 IBM Corporation and others.
 4718%; All rights reserved. This program and the accompanying materials
 4719%; are made available under the terms of the Common Public License v1.0
 4720%; which accompanies this distribution, and is available at
 4721%; http://www.eclipse.org/legal/cpl-v10.html
 4722%;
 4723%; Contributors:
 4724%; IBM - Initial implementation
 4725%;
 4726%; @book{Mueller:2006,
 4727%;   author = "Erik T. Mueller",
 4728%;   year = "2006",
 4729%;   title = "Commonsense Reasoning",
 4730%;   address = "San Francisco",
 4731%;   publisher = "Morgan Kaufmann/Elsevier",
 4732%; }
 4733%;
 4734
 4735% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1182
 4736% load foundations/Root.e
 4737
 4738% load foundations/EC.e
 4739
 4740% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1185
 4741% sort agent
 4742% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1186
 4743==> sort(agent).
 4744
 4745% agent Nathan
 4746% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1188
 4747==> t(agent,nathan).
 4748
 4749% fluent Awake(agent)
 4750 %  fluent(awake(agent)).
 4751% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1190
 4752==> mpred_prop(awake(agent),fluent).
 4753==> meta_argtypes(awake(agent)).
 4754
 4755% event WakeUp(agent)
 4756 %  event(wakeUp(agent)).
 4757% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1192
 4758==> mpred_prop(wakeUp(agent),event).
 4759==> meta_argtypes(wakeUp(agent)).
 4760
 4761% event FallAsleep(agent)
 4762 %  event(fallAsleep(agent)).
 4763% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1193
 4764==> mpred_prop(fallAsleep(agent),event).
 4765==> meta_argtypes(fallAsleep(agent)).
 4766
 4767
 4768% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1194
 4769%; Sigma
 4770% [agent,time]
 4771 % Initiates(WakeUp(agent),Awake(agent),time).
 4772% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1196
 4773axiom(initiates(wakeUp(Agent), awake(Agent), Time),
 4774    []).
 4775
 4776
 4777% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1197
 4778% [agent,time]
 4779 % Terminates(FallAsleep(agent),Awake(agent),time).
 4780axiom(terminates(fallAsleep(Agent), awake(Agent), Time),
 4781    []).
 4782
 4783
 4784% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1199
 4785%; Delta
 4786
 4787
 4788% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1201
 4789% Happens(WakeUp(Nathan),1).
 4790axiom(happens(wakeUp(nathan), start),
 4791    [is_time(1), b(t, start), ignore(t+1=start)]).
 4792
 4793
 4794% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1203
 4795%; Gamma
 4796
 4797
 4798% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1205
 4799% !HoldsAt(Awake(Nathan),0).
 4800 %  not(initially(awake(nathan))).
 4801axiom(not(initially(awake(nathan))),
 4802    []).
 4803
 4804
 4805% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1207
 4806%; entailed:
 4807%; HoldsAt(Awake(Nathan),3).
 4808
 4809% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1210
 4810% completion Happens
 4811% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1211
 4812==> completion(happens).
 4813
 4814% range time 0 3
 4815% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1213
 4816==> range(time,0,3).
 4817
 4818% range offset 1 1
 4819% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1214
 4820==> range(offset,1,1).
 4821%; End of file.
 4822%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4823%; FILE: examples/Mueller2006/Chapter2/Sleep3.e
 4824%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4825%;
 4826%; Copyright (c) 2005 IBM Corporation and others.
 4827%; All rights reserved. This program and the accompanying materials
 4828%; are made available under the terms of the Common Public License v1.0
 4829%; which accompanies this distribution, and is available at
 4830%; http://www.eclipse.org/legal/cpl-v10.html
 4831%;
 4832%; Contributors:
 4833%; IBM - Initial implementation
 4834%;
 4835%; @book{Mueller:2006,
 4836%;   author = "Erik T. Mueller",
 4837%;   year = "2006",
 4838%;   title = "Commonsense Reasoning",
 4839%;   address = "San Francisco",
 4840%;   publisher = "Morgan Kaufmann/Elsevier",
 4841%; }
 4842%;
 4843
 4844% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1241
 4845% load foundations/Root.e
 4846
 4847% load foundations/EC.e
 4848
 4849% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1244
 4850% sort agent
 4851% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1245
 4852==> sort(agent).
 4853
 4854% agent Nathan
 4855% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1247
 4856==> t(agent,nathan).
 4857
 4858% fluent Awake(agent)
 4859 %  fluent(awake(agent)).
 4860% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1249
 4861==> mpred_prop(awake(agent),fluent).
 4862==> meta_argtypes(awake(agent)).
 4863
 4864% event WakeUp(agent)
 4865 %  event(wakeUp(agent)).
 4866% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1251
 4867==> mpred_prop(wakeUp(agent),event).
 4868==> meta_argtypes(wakeUp(agent)).
 4869
 4870% event FallAsleep(agent)
 4871 %  event(fallAsleep(agent)).
 4872% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1252
 4873==> mpred_prop(fallAsleep(agent),event).
 4874==> meta_argtypes(fallAsleep(agent)).
 4875
 4876
 4877% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1253
 4878%; Sigma
 4879% [agent,time]
 4880 % Initiates(WakeUp(agent),Awake(agent),time).
 4881% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1255
 4882axiom(initiates(wakeUp(Agent), awake(Agent), Time),
 4883    []).
 4884
 4885
 4886% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1256
 4887% [agent,time]
 4888 % Terminates(FallAsleep(agent),Awake(agent),time).
 4889axiom(terminates(fallAsleep(Agent), awake(Agent), Time),
 4890    []).
 4891
 4892
 4893% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1258
 4894%; Delta
 4895% [agent,time]
 4896% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1261
 4897% Happens(WakeUp(agent),time) ->
 4898% !HoldsAt(Awake(agent),time).
 4899% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1262
 4900axiom(requires(wakeUp(Agent), Time),
 4901    [not(holds_at(awake(Agent), Time))]).
 4902
 4903
 4904% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1264
 4905% Happens(WakeUp(Nathan),0).
 4906axiom(happens(wakeUp(nathan), t),
 4907    [is_time(0)]).
 4908
 4909
 4910% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1266
 4911%; Gamma
 4912
 4913
 4914% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1268
 4915% HoldsAt(Awake(Nathan),1).
 4916holds_at(awake(nathan),1).
 4917
 4918
 4919% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1270
 4920%; inferred:
 4921%; !HoldsAt(Awake(Nathan),0).
 4922
 4923% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1273
 4924% completion Happens
 4925% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1274
 4926==> completion(happens).
 4927
 4928% range time 0 1
 4929% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1276
 4930==> range(time,0,1).
 4931
 4932% range offset 1 1
 4933% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1277
 4934==> range(offset,1,1).
 4935%; End of file.
 4936%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4937%; FILE: examples/Mueller2006/Chapter2/Inconsistency3.e
 4938%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 4939%;
 4940%; Copyright (c) 2005 IBM Corporation and others.
 4941%; All rights reserved. This program and the accompanying materials
 4942%; are made available under the terms of the Common Public License v1.0
 4943%; which accompanies this distribution, and is available at
 4944%; http://www.eclipse.org/legal/cpl-v10.html
 4945%;
 4946%; Contributors:
 4947%; IBM - Initial implementation
 4948%;
 4949%; @book{Mueller:2006,
 4950%;   author = "Erik T. Mueller",
 4951%;   year = "2006",
 4952%;   title = "Commonsense Reasoning",
 4953%;   address = "San Francisco",
 4954%;   publisher = "Morgan Kaufmann/Elsevier",
 4955%; }
 4956%;
 4957
 4958% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1304
 4959% load foundations/Root.e
 4960
 4961% load foundations/EC.e
 4962
 4963% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1307
 4964% sort object
 4965% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1308
 4966==> sort(object).
 4967
 4968% object O1
 4969% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1309
 4970==> t(object,o1).
 4971
 4972% fluent F(object)
 4973 %  fluent(f(object)).
 4974% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1311
 4975==> mpred_prop(f(object),fluent).
 4976==> meta_argtypes(f(object)).
 4977
 4978% event E(object)
 4979 %  event(e(object)).
 4980% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1313
 4981==> mpred_prop(e(object),event).
 4982==> meta_argtypes(e(object)).
 4983
 4984
 4985% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1314
 4986% [object,time]
 4987 % Releases(E(object),F(object),time).
 4988axiom(releases(e(Object), f(Object), Time),
 4989    []).
 4990
 4991
 4992% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1315
 4993% [object,time]
 4994 % Terminates(E(object),F(object),time).
 4995axiom(terminates(e(Object), f(Object), Time),
 4996    []).
 4997
 4998
 4999% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1317
 5000% Happens(E(O1),0).
 5001axiom(happens(e(o1), t),
 5002    [is_time(0)]).
 5003
 5004% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1319
 5005% range time 0 1
 5006% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1320
 5007==> range(time,0,1).
 5008
 5009% range offset 1 1
 5010% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1321
 5011==> range(offset,1,1).
 5012%; End of file.
 5013%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5014%; FILE: examples/Mueller2006/Chapter2/Sleep4.e
 5015%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5016%;
 5017%; Copyright (c) 2005 IBM Corporation and others.
 5018%; All rights reserved. This program and the accompanying materials
 5019%; are made available under the terms of the Common Public License v1.0
 5020%; which accompanies this distribution, and is available at
 5021%; http://www.eclipse.org/legal/cpl-v10.html
 5022%;
 5023%; Contributors:
 5024%; IBM - Initial implementation
 5025%;
 5026%; @book{Mueller:2006,
 5027%;   author = "Erik T. Mueller",
 5028%;   year = "2006",
 5029%;   title = "Commonsense Reasoning",
 5030%;   address = "San Francisco",
 5031%;   publisher = "Morgan Kaufmann/Elsevier",
 5032%; }
 5033%;
 5034
 5035% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1348
 5036% load foundations/Root.e
 5037
 5038% load foundations/EC.e
 5039
 5040% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1351
 5041% sort agent
 5042% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1352
 5043==> sort(agent).
 5044
 5045% agent Nathan
 5046% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1354
 5047==> t(agent,nathan).
 5048
 5049% fluent Awake(agent)
 5050 %  fluent(awake(agent)).
 5051% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1356
 5052==> mpred_prop(awake(agent),fluent).
 5053==> meta_argtypes(awake(agent)).
 5054
 5055% event WakeUp(agent)
 5056 %  event(wakeUp(agent)).
 5057% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1358
 5058==> mpred_prop(wakeUp(agent),event).
 5059==> meta_argtypes(wakeUp(agent)).
 5060
 5061% event FallAsleep(agent)
 5062 %  event(fallAsleep(agent)).
 5063% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1359
 5064==> mpred_prop(fallAsleep(agent),event).
 5065==> meta_argtypes(fallAsleep(agent)).
 5066
 5067
 5068% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1360
 5069%; Sigma
 5070% [agent,time]
 5071 % Initiates(WakeUp(agent),Awake(agent),time).
 5072% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1362
 5073axiom(initiates(wakeUp(Agent), awake(Agent), Time),
 5074    []).
 5075
 5076
 5077% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1363
 5078% [agent,time]
 5079 % Terminates(FallAsleep(agent),Awake(agent),time).
 5080axiom(terminates(fallAsleep(Agent), awake(Agent), Time),
 5081    []).
 5082
 5083
 5084% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1365
 5085%; Delta
 5086
 5087
 5088% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1367
 5089% Happens(WakeUp(Nathan),1).
 5090axiom(happens(wakeUp(nathan), start),
 5091    [is_time(1), b(t, start), ignore(t+1=start)]).
 5092
 5093
 5094% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1369
 5095%; entailed:
 5096%; HoldsAt(Awake(Nathan),3).
 5097
 5098% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1372
 5099% completion Happens
 5100% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1373
 5101==> completion(happens).
 5102
 5103% range time 0 3
 5104% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1375
 5105==> range(time,0,3).
 5106
 5107% range offset 1 1
 5108% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1376
 5109==> range(offset,1,1).
 5110%; End of file.
 5111%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5112%; FILE: examples/Mueller2006/Chapter2/Inconsistency4.e
 5113%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5114%;
 5115%; Copyright (c) 2005 IBM Corporation and others.
 5116%; All rights reserved. This program and the accompanying materials
 5117%; are made available under the terms of the Common Public License v1.0
 5118%; which accompanies this distribution, and is available at
 5119%; http://www.eclipse.org/legal/cpl-v10.html
 5120%;
 5121%; Contributors:
 5122%; IBM - Initial implementation
 5123%;
 5124%; @book{Mueller:2006,
 5125%;   author = "Erik T. Mueller",
 5126%;   year = "2006",
 5127%;   title = "Commonsense Reasoning",
 5128%;   address = "San Francisco",
 5129%;   publisher = "Morgan Kaufmann/Elsevier",
 5130%; }
 5131%;
 5132
 5133% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1403
 5134% load foundations/Root.e
 5135
 5136% load foundations/EC.e
 5137
 5138% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1406
 5139% sort object
 5140% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1407
 5141==> sort(object).
 5142
 5143% object O1
 5144% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1408
 5145==> t(object,o1).
 5146
 5147% event E(object)
 5148 %  event(e(object)).
 5149% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1410
 5150==> mpred_prop(e(object),event).
 5151==> meta_argtypes(e(object)).
 5152
 5153% fluent F1(object)
 5154 %  fluent(f1(object)).
 5155% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1412
 5156==> mpred_prop(f1(object),fluent).
 5157==> meta_argtypes(f1(object)).
 5158
 5159% fluent F2(object)
 5160 %  fluent(f2(object)).
 5161% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1413
 5162==> mpred_prop(f2(object),fluent).
 5163==> meta_argtypes(f2(object)).
 5164
 5165
 5166% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1414
 5167% [object,time]
 5168% Initiates(E(object),F1(object),time).
 5169% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1415
 5170axiom(initiates(e(Object), f1(Object), Time),
 5171    []).
 5172
 5173
 5174% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1417
 5175% [object,time]
 5176% HoldsAt(F1(object),time) <-> HoldsAt(F2(object),time).
 5177
 5178 /*  holds_at(f1(Object), Time) <->
 5179       holds_at(f2(Object), Time).
 5180 */
 5181% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1418
 5182axiom(holds_at(f1(Object), Time),
 5183    [holds_at(f2(Object), Time)]).
 5184axiom(holds_at(f2(Object), Time),
 5185    [holds_at(f1(Object), Time)]).
 5186
 5187
 5188% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1420
 5189% !HoldsAt(F2(O1),0).
 5190 %  not(initially(f2(o1))).
 5191axiom(not(initially(f2(o1))),
 5192    []).
 5193
 5194
 5195% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1421
 5196% Happens(E(O1),0).
 5197axiom(happens(e(o1), t),
 5198    [is_time(0)]).
 5199
 5200% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1423
 5201% range time 0 1
 5202% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1424
 5203==> range(time,0,1).
 5204
 5205% range offset 1 1
 5206% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1425
 5207==> range(offset,1,1).
 5208%; End of file.
 5209%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5210%; FILE: examples/Mueller2006/Chapter2/Inconsistency1.e
 5211%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5212%;
 5213%; Copyright (c) 2005 IBM Corporation and others.
 5214%; All rights reserved. This program and the accompanying materials
 5215%; are made available under the terms of the Common Public License v1.0
 5216%; which accompanies this distribution, and is available at
 5217%; http://www.eclipse.org/legal/cpl-v10.html
 5218%;
 5219%; Contributors:
 5220%; IBM - Initial implementation
 5221%;
 5222%; @book{Mueller:2006,
 5223%;   author = "Erik T. Mueller",
 5224%;   year = "2006",
 5225%;   title = "Commonsense Reasoning",
 5226%;   address = "San Francisco",
 5227%;   publisher = "Morgan Kaufmann/Elsevier",
 5228%; }
 5229%;
 5230
 5231% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1452
 5232% load foundations/Root.e
 5233
 5234% load foundations/EC.e
 5235
 5236% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1455
 5237% sort object
 5238% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1456
 5239==> sort(object).
 5240
 5241% object O1
 5242% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1457
 5243==> t(object,o1).
 5244
 5245% fluent F(object)
 5246 %  fluent(f(object)).
 5247% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1459
 5248==> mpred_prop(f(object),fluent).
 5249==> meta_argtypes(f(object)).
 5250
 5251% event E(object)
 5252 %  event(e(object)).
 5253% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1461
 5254==> mpred_prop(e(object),event).
 5255==> meta_argtypes(e(object)).
 5256
 5257
 5258% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1462
 5259% [object,time]
 5260 % Initiates(E(object),F(object),time).
 5261axiom(initiates(e(Object), f(Object), Time),
 5262    []).
 5263
 5264
 5265% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1463
 5266% [object,time]
 5267 % Terminates(E(object),F(object),time).
 5268axiom(terminates(e(Object), f(Object), Time),
 5269    []).
 5270
 5271
 5272% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1465
 5273% Happens(E(O1),0).
 5274axiom(happens(e(o1), t),
 5275    [is_time(0)]).
 5276
 5277% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1467
 5278% range time 0 1
 5279% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1468
 5280==> range(time,0,1).
 5281
 5282% range offset 1 1
 5283% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1469
 5284==> range(offset,1,1).
 5285%; End of file.
 5286%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5287%; FILE: examples/Mueller2006/Chapter2/Inconsistency2.e
 5288%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5289%;
 5290%; Copyright (c) 2005 IBM Corporation and others.
 5291%; All rights reserved. This program and the accompanying materials
 5292%; are made available under the terms of the Common Public License v1.0
 5293%; which accompanies this distribution, and is available at
 5294%; http://www.eclipse.org/legal/cpl-v10.html
 5295%;
 5296%; Contributors:
 5297%; IBM - Initial implementation
 5298%;
 5299%; @book{Mueller:2006,
 5300%;   author = "Erik T. Mueller",
 5301%;   year = "2006",
 5302%;   title = "Commonsense Reasoning",
 5303%;   address = "San Francisco",
 5304%;   publisher = "Morgan Kaufmann/Elsevier",
 5305%; }
 5306%;
 5307
 5308% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1496
 5309% load foundations/Root.e
 5310
 5311% load foundations/EC.e
 5312
 5313% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1499
 5314% sort object
 5315% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1500
 5316==> sort(object).
 5317
 5318% object O1
 5319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1501
 5320==> t(object,o1).
 5321
 5322% fluent F(object)
 5323 %  fluent(f(object)).
 5324% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1503
 5325==> mpred_prop(f(object),fluent).
 5326==> meta_argtypes(f(object)).
 5327
 5328% event E(object)
 5329 %  event(e(object)).
 5330% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1505
 5331==> mpred_prop(e(object),event).
 5332==> meta_argtypes(e(object)).
 5333
 5334
 5335% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1506
 5336% [object,time]
 5337 % Releases(E(object),F(object),time).
 5338axiom(releases(e(Object), f(Object), Time),
 5339    []).
 5340
 5341
 5342% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1507
 5343% [object,time]
 5344 % Initiates(E(object),F(object),time).
 5345axiom(initiates(e(Object), f(Object), Time),
 5346    []).
 5347
 5348
 5349% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1509
 5350% Happens(E(O1),0).
 5351axiom(happens(e(o1), t),
 5352    [is_time(0)]).
 5353
 5354% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1511
 5355% range time 0 1
 5356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1512
 5357==> range(time,0,1).
 5358
 5359% range offset 1 1
 5360% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1513
 5361==> range(offset,1,1).
 5362%; End of file.
 5363%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5364%; FILE: examples/Mueller2006/Chapter8/CameraWithFlash.e
 5365%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5366%;
 5367%; Copyright (c) 2005 IBM Corporation and others.
 5368%; All rights reserved. This program and the accompanying materials
 5369%; are made available under the terms of the Common Public License v1.0
 5370%; which accompanies this distribution, and is available at
 5371%; http://www.eclipse.org/legal/cpl-v10.html
 5372%;
 5373%; Contributors:
 5374%; IBM - Initial implementation
 5375%;
 5376%; @book{Mueller:2006,
 5377%;   author = "Erik T. Mueller",
 5378%;   year = "2006",
 5379%;   title = "Commonsense Reasoning",
 5380%;   address = "San Francisco",
 5381%;   publisher = "Morgan Kaufmann/Elsevier",
 5382%; }
 5383%;
 5384
 5385% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1540
 5386% load foundations/Root.e
 5387
 5388% load foundations/EC.e
 5389
 5390% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1543
 5391% sort camera
 5392% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1544
 5393==> sort(camera).
 5394
 5395% camera Camera1
 5396% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1546
 5397==> t(camera,camera1).
 5398
 5399% fluent ProperlyExposedPicture(camera)
 5400 %  fluent(properlyExposedPicture(camera)).
 5401% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1548
 5402==> mpred_prop(properlyExposedPicture(camera),fluent).
 5403==> meta_argtypes(properlyExposedPicture(camera)).
 5404
 5405% fluent ImproperlyExposedPicture(camera)
 5406 %  fluent(improperlyExposedPicture(camera)).
 5407% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1549
 5408==> mpred_prop(improperlyExposedPicture(camera),fluent).
 5409==> meta_argtypes(improperlyExposedPicture(camera)).
 5410
 5411% event ReleaseShutter(camera)
 5412 %  event(releaseShutter(camera)).
 5413% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1551
 5414==> mpred_prop(releaseShutter(camera),event).
 5415==> meta_argtypes(releaseShutter(camera)).
 5416
 5417% event TriggerFlash(camera)
 5418 %  event(triggerFlash(camera)).
 5419% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1552
 5420==> mpred_prop(triggerFlash(camera),event).
 5421==> meta_argtypes(triggerFlash(camera)).
 5422
 5423
 5424% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1553
 5425%; Sigma
 5426% [camera,time]
 5427% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1556
 5428% Happens(TriggerFlash(camera),time) ->
 5429% Initiates(ReleaseShutter(camera),ProperlyExposedPicture(camera),time).
 5430% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1557
 5431axiom(requires(triggerFlash(Camera), Time),
 5432   
 5433    [ initiates(releaseShutter(Camera),
 5434                properlyExposedPicture(Camera),
 5435                Time)
 5436    ]).
 5437
 5438
 5439% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1559
 5440% [camera,time]
 5441% !Happens(TriggerFlash(camera),time) ->
 5442% Initiates(ReleaseShutter(camera),ImproperlyExposedPicture(camera),time).
 5443% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1561
 5444axiom(initiates(releaseShutter(Camera), improperlyExposedPicture(Camera), Time),
 5445    [not(happens(triggerFlash(Camera), Time))]).
 5446
 5447
 5448% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1563
 5449%; Delta
 5450
 5451% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1565
 5452% Delta: 
 5453next_axiom_uses(delta).
 5454 
 5455
 5456
 5457% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1565
 5458% Happens(ReleaseShutter(Camera1),0).
 5459axiom(happens(releaseShutter(camera1), t),
 5460    [is_time(0)]).
 5461
 5462% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1566
 5463% Delta: 
 5464next_axiom_uses(delta).
 5465 
 5466
 5467
 5468% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1566
 5469% Happens(TriggerFlash(Camera1),1).
 5470axiom(happens(triggerFlash(camera1), start),
 5471    [is_time(1), b(t, start), ignore(t+1=start)]).
 5472
 5473% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1567
 5474% Delta: 
 5475next_axiom_uses(delta).
 5476 
 5477
 5478
 5479% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1567
 5480% Happens(ReleaseShutter(Camera1),1).
 5481axiom(happens(releaseShutter(camera1), start),
 5482    [is_time(1), b(t, start), ignore(t+1=start)]).
 5483
 5484
 5485% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1569
 5486%; added:
 5487% [camera]
 5488 % !HoldsAt(ImproperlyExposedPicture(camera),0).
 5489 %  not(initially(improperlyExposedPicture(Camera))).
 5490% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1570
 5491axiom(not(initially(improperlyExposedPicture(ImproperlyExposedPicture_Ret))),
 5492    []).
 5493
 5494
 5495% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1571
 5496% [camera]
 5497 % !HoldsAt(ProperlyExposedPicture(camera),0).
 5498 %  not(initially(properlyExposedPicture(Camera))).
 5499axiom(not(initially(properlyExposedPicture(ProperlyExposedPicture_Ret))),
 5500    []).
 5501
 5502% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1573
 5503% completion Delta Happens
 5504% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1574
 5505==> completion(delta).
 5506==> completion(happens).
 5507
 5508% range time 0 2
 5509% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1576
 5510==> range(time,0,2).
 5511
 5512% range offset 1 1
 5513% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1577
 5514==> range(offset,1,1).
 5515%; End of file.
 5516%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5517%; FILE: examples/Mueller2006/Chapter8/MovingRobot.e
 5518%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5519%;
 5520%; Copyright (c) 2005 IBM Corporation and others.
 5521%; All rights reserved. This program and the accompanying materials
 5522%; are made available under the terms of the Common Public License v1.0
 5523%; which accompanies this distribution, and is available at
 5524%; http://www.eclipse.org/legal/cpl-v10.html
 5525%;
 5526%; Contributors:
 5527%; IBM - Initial implementation
 5528%;
 5529%; @inproceedings{Shanahan:1996,
 5530%;   author = "Murray Shanahan",
 5531%;   year = "1996",
 5532%;   title = "Robotics and the common sense informatic situation",
 5533%;   editor = "Wolfgang Wahlster",
 5534%;   booktitle = "\uppercase{P}roceedings of the \uppercase{T}welfth \uppercase{E}uropean \uppercase{C}onference on \uppercase{A}rtificial \uppercase{I}ntelligence",
 5535%;   pages = "684--688",
 5536%;   address = "Chichester, UK",
 5537%;   publisher = "John Wiley",
 5538%; }
 5539%;
 5540%; @book{Mueller:2006,
 5541%;   author = "Erik T. Mueller",
 5542%;   year = "2006",
 5543%;   title = "Commonsense Reasoning",
 5544%;   address = "San Francisco",
 5545%;   publisher = "Morgan Kaufmann/Elsevier",
 5546%; }
 5547%;
 5548
 5549% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1615
 5550% option renaming off
 5551% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1616
 5552:- set_ec_option(renaming, off). 5553
 5554% load foundations/Root.e
 5555
 5556% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1618
 5557% load foundations/EC.e
 5558
 5559% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1620
 5560% sort coord: integer
 5561% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1621
 5562==> subsort(coord,integer).
 5563
 5564% sort direction: integer
 5565% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1623
 5566==> subsort(direction,integer).
 5567%; 0 -> 0, 1 -> 90, 2 -> 180, 3 -> 370
 5568
 5569% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1625
 5570% sort robot
 5571% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1626
 5572==> sort(robot).
 5573
 5574% robot Robot1
 5575% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1628
 5576==> t(robot,robot1).
 5577
 5578% function Sin(direction): coord
 5579 %  functional_predicate(sin(direction,coord)).
 5580% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1630
 5581==> mpred_prop(sin(direction,coord),functional_predicate).
 5582==> meta_argtypes(sin(direction,coord)).
 5583resultIsa(sin,coord).
 5584
 5585% function Cos(direction): coord
 5586 %  functional_predicate(cos(direction,coord)).
 5587% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1631
 5588==> mpred_prop(cos(direction,coord),functional_predicate).
 5589==> meta_argtypes(cos(direction,coord)).
 5590resultIsa(cos,coord).
 5591
 5592
 5593% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1632
 5594% Sin(0)=0.
 5595sin(0,0).
 5596
 5597
 5598% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1633
 5599% Sin(1)=1.
 5600sin(1,1).
 5601
 5602
 5603% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1634
 5604% Sin(2)=2.
 5605sin(2,2).
 5606
 5607
 5608% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1635
 5609% Sin(3)=3.
 5610sin(3,3).
 5611
 5612
 5613% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1637
 5614% Cos(0)=1.
 5615cos(0,1).
 5616
 5617
 5618% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1638
 5619% Cos(1)=2.
 5620cos(1,2).
 5621
 5622
 5623% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1639
 5624% Cos(2)=3.
 5625cos(2,3).
 5626
 5627
 5628% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1640
 5629% Cos(3)=4.
 5630cos(3,4).
 5631
 5632% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1642
 5633% fluent Direction(robot,direction)
 5634 %  fluent(direction(robot,direction)).
 5635% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1643
 5636==> mpred_prop(direction(robot,direction),fluent).
 5637==> meta_argtypes(direction(robot,direction)).
 5638
 5639% fluent Location(robot,coord,coord)
 5640 %  fluent(location(robot,coord,coord)).
 5641% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1644
 5642==> mpred_prop(location(robot,coord,coord),fluent).
 5643==> meta_argtypes(location(robot,coord,coord)).
 5644
 5645% event MoveLeftWheel(robot)
 5646 %  event(moveLeftWheel(robot)).
 5647% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1646
 5648==> mpred_prop(moveLeftWheel(robot),event).
 5649==> meta_argtypes(moveLeftWheel(robot)).
 5650
 5651% event MoveRightWheel(robot)
 5652 %  event(moveRightWheel(robot)).
 5653% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1647
 5654==> mpred_prop(moveRightWheel(robot),event).
 5655==> meta_argtypes(moveRightWheel(robot)).
 5656
 5657
 5658% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1648
 5659%; Sigma
 5660% [robot,direction1,direction2,time]
 5661% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1651
 5662% !Happens(MoveRightWheel(robot),time) &
 5663% HoldsAt(Direction(robot,direction1),time) &
 5664% direction2 = (direction1-1)->
 5665% Initiates(MoveLeftWheel(robot),Direction(robot,direction2),time).
 5666% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1654
 5667axiom(initiates(moveLeftWheel(Robot), direction(Robot, Direction2), Time),
 5668   
 5669    [ not(happens(moveRightWheel(Robot), Time)),
 5670      holds_at(direction(Robot, Direction1), Time),
 5671      equals(Direction2, Direction1-1)
 5672    ]).
 5673
 5674
 5675% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1656
 5676% [robot,direction,time]
 5677% !Happens(MoveRightWheel(robot),time) &
 5678% HoldsAt(Direction(robot,direction),time) ->
 5679% Terminates(MoveLeftWheel(robot),Direction(robot,direction),time).
 5680% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1659
 5681axiom(terminates(moveLeftWheel(Robot), direction(Robot, Direction), Time),
 5682   
 5683    [ not(happens(moveRightWheel(Robot), Time)),
 5684      holds_at(direction(Robot, Direction), Time)
 5685    ]).
 5686
 5687
 5688% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1661
 5689% [robot,direction1,direction2,time]
 5690% !Happens(MoveLeftWheel(robot),time) &
 5691% HoldsAt(Direction(robot,direction1),time) &
 5692% direction2 = (direction1+1)->
 5693% Initiates(MoveRightWheel(robot),Direction(robot,direction2),time).
 5694% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1665
 5695axiom(initiates(moveRightWheel(Robot), direction(Robot, Direction2), Time),
 5696   
 5697    [ not(happens(moveLeftWheel(Robot), Time)),
 5698      holds_at(direction(Robot, Direction1), Time),
 5699      equals(Direction2, Direction1+1)
 5700    ]).
 5701
 5702
 5703% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1667
 5704% [robot,direction,time]
 5705% !Happens(MoveLeftWheel(robot),time) &
 5706% HoldsAt(Direction(robot,direction),time) ->
 5707% Terminates(MoveRightWheel(robot),Direction(robot,direction),time).
 5708% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1670
 5709axiom(terminates(moveRightWheel(Robot), direction(Robot, Direction), Time),
 5710   
 5711    [ not(happens(moveLeftWheel(Robot), Time)),
 5712      holds_at(direction(Robot, Direction), Time)
 5713    ]).
 5714
 5715
 5716% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1672
 5717% [robot,direction,coord1,coord2,coord3,coord4,time]
 5718% Happens(MoveLeftWheel(robot),time) &
 5719% HoldsAt(Location(robot,coord1,coord2),time) &
 5720% HoldsAt(Direction(robot,direction),time) &
 5721% coord3 = coord1+Cos(direction) &
 5722% coord4 = coord2+Sin(direction) ->
 5723% Initiates(MoveRightWheel(robot),
 5724%           Location(robot,coord3,coord4),
 5725%           time).
 5726% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1680
 5727axiom(initiates(moveRightWheel(Robot), location(Robot, Coord3, Coord4), Time),
 5728   
 5729    [ happens(moveLeftWheel(Robot), Time),
 5730      holds_at(location(Robot, Coord1, Coord2), Time),
 5731      holds_at(direction(Robot, Direction), Time),
 5732      equals(Coord3, Coord1+cos(Direction)),
 5733      equals(Coord4, Coord2+sin(Direction))
 5734    ]).
 5735
 5736
 5737% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1682
 5738% [robot,coord1,coord2,time]
 5739% Happens(MoveLeftWheel(robot),time) &
 5740% HoldsAt(Location(robot,coord1,coord2),time) ->
 5741%; FIX: Direction not needed!!
 5742%; HoldsAt(Direction(robot,direction),time) ->
 5743% Terminates(MoveRightWheel(robot),Location(robot,coord1,coord2),time).
 5744% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1687
 5745axiom(terminates(moveRightWheel(Robot), location(Robot, Coord1, Coord2), Time),
 5746   
 5747    [ happens(moveLeftWheel(Robot), Time),
 5748      holds_at(location(Robot, Coord1, Coord2), Time)
 5749    ]).
 5750
 5751
 5752% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1689
 5753%; Delta
 5754
 5755
 5756% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1691
 5757% Happens(MoveRightWheel(Robot1),0).
 5758axiom(happens(moveRightWheel(robot1), t),
 5759    [is_time(0)]).
 5760
 5761
 5762% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1692
 5763% Happens(MoveLeftWheel(Robot1),1).
 5764axiom(happens(moveLeftWheel(robot1), start),
 5765    [is_time(1), b(t, start), ignore(t+1=start)]).
 5766
 5767
 5768% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1693
 5769% Happens(MoveRightWheel(Robot1),1).
 5770axiom(happens(moveRightWheel(robot1), start),
 5771    [is_time(1), b(t, start), ignore(t+1=start)]).
 5772
 5773
 5774% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1695
 5775%; Psi
 5776% [robot,coord1,coord2,coord3,coord4,time]
 5777% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1699
 5778% HoldsAt(Location(robot,coord1,coord2),time) &
 5779% HoldsAt(Location(robot,coord3,coord4),time) ->
 5780% coord1=coord3 &
 5781% coord2=coord4.
 5782
 5783 /*   if((holds_at(location(Robot, Coord1, Coord2), Time), holds_at(location(Robot, Coord3, Coord4), Time)),
 5784          (Coord1=Coord3, Coord2=Coord4)).
 5785 */
 5786
 5787 /*  not(holds_at(location(Location_Param, Equals_Param, Equals_Param9), Time6)) :-
 5788       holds_at(location(Location_Param,
 5789                         Equals_Ret,
 5790                         Location_Ret),
 5791                Time6),
 5792       (   not(equals(Equals_Param, Equals_Ret))
 5793       ;   not(equals(Equals_Param9, Location_Ret))
 5794       ).
 5795 */
 5796% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1702
 5797axiom(not(holds_at(location(Location_Param, Equals_Param, Equals_Param9), Time6)),
 5798   
 5799    [ not(equals(Equals_Param, Equals_Ret)),
 5800      holds_at(location(Location_Param,
 5801                        Equals_Ret,
 5802                        Location_Ret),
 5803               Time6)
 5804    ]).
 5805axiom(not(holds_at(location(Location_Param, Equals_Param, Equals_Param9), Time6)),
 5806   
 5807    [ not(equals(Equals_Param9, Location_Ret)),
 5808      holds_at(location(Location_Param,
 5809                        Equals_Ret,
 5810                        Location_Ret),
 5811               Time6)
 5812    ]).
 5813
 5814 /*  not(holds_at(location(Location_Param13, Equals_Ret17, Location_Ret16), Time12)) :-
 5815       holds_at(location(Location_Param13,
 5816                         Equals_Param14,
 5817                         Equals_Param15),
 5818                Time12),
 5819       (   not(equals(Equals_Param14, Equals_Ret17))
 5820       ;   not(equals(Equals_Param15, Location_Ret16))
 5821       ).
 5822 */
 5823axiom(not(holds_at(location(Location_Param13, Equals_Ret17, Location_Ret16), Time12)),
 5824   
 5825    [ not(equals(Equals_Param14, Equals_Ret17)),
 5826      holds_at(location(Location_Param13,
 5827                        Equals_Param14,
 5828                        Equals_Param15),
 5829               Time12)
 5830    ]).
 5831axiom(not(holds_at(location(Location_Param13, Equals_Ret17, Location_Ret16), Time12)),
 5832   
 5833    [ not(equals(Equals_Param15, Location_Ret16)),
 5834      holds_at(location(Location_Param13,
 5835                        Equals_Param14,
 5836                        Equals_Param15),
 5837               Time12)
 5838    ]).
 5839
 5840 /*  equals(Equals_Param19, Equals_Ret21) :-
 5841       holds_at(location(Location_Param20,
 5842                         Equals_Param19,
 5843                         Location_Ret22),
 5844                Time18),
 5845       holds_at(location(Location_Param20,
 5846                         Equals_Ret21,
 5847                         Location_Ret23),
 5848                Time18).
 5849 */
 5850axiom(equals(Equals_Param19, Equals_Ret21),
 5851   
 5852    [ holds_at(location(Location_Param20,
 5853                        Equals_Param19,
 5854                        Location_Ret22),
 5855               Time18),
 5856      holds_at(location(Location_Param20,
 5857                        Equals_Ret21,
 5858                        Location_Ret23),
 5859               Time18)
 5860    ]).
 5861
 5862 /*  equals(Equals_Param25, Equals_Ret27) :-
 5863       holds_at(location(Location_Param26, _, Equals_Param25),
 5864                Time24),
 5865       holds_at(location(Location_Param26, _, Equals_Ret27),
 5866                Time24).
 5867 */
 5868axiom(equals(Equals_Param25, Equals_Ret27),
 5869   
 5870    [ holds_at(location(Location_Param26, _, Equals_Param25),
 5871               Time24),
 5872      holds_at(location(Location_Param26, _, Equals_Ret27),
 5873               Time24)
 5874    ]).
 5875
 5876
 5877% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1704
 5878% [robot,direction1,direction2,time]
 5879% HoldsAt(Direction(robot,direction1),time) &
 5880% HoldsAt(Direction(robot,direction2),time) ->
 5881% direction1=direction2.
 5882% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1707
 5883axiom(Direction1=Direction2,
 5884   
 5885    [ holds_at(direction(Robot, Direction1), Time),
 5886      holds_at(direction(Robot, Direction2), Time)
 5887    ]).
 5888
 5889
 5890% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1709
 5891%; Gamma
 5892
 5893
 5894% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1711
 5895% HoldsAt(Location(Robot1,0,0),0).
 5896axiom(initially(location(robot1, 0, 0)),
 5897    []).
 5898
 5899
 5900% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1712
 5901% HoldsAt(Direction(Robot1,0),0).
 5902axiom(initially(direction(robot1, 0)),
 5903    []).
 5904
 5905% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1714
 5906% completion Happens
 5907% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1715
 5908==> completion(happens).
 5909
 5910% range time 0 3
 5911% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1717
 5912==> range(time,0,3).
 5913
 5914% range coord 0 3
 5915% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1718
 5916==> range(coord,0,3).
 5917
 5918% range direction 0 3
 5919% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1719
 5920==> range(direction,0,3).
 5921
 5922% range offset 1 1
 5923% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1720
 5924==> range(offset,1,1).
 5925%; End of file.
 5926%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5927%; FILE: examples/Mueller2006/Chapter8/PatHeadRubStomach.e
 5928%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 5929%;
 5930%; Copyright (c) 2005 IBM Corporation and others.
 5931%; All rights reserved. This program and the accompanying materials
 5932%; are made available under the terms of the Common Public License v1.0
 5933%; which accompanies this distribution, and is available at
 5934%; http://www.eclipse.org/legal/cpl-v10.html
 5935%;
 5936%; Contributors:
 5937%; IBM - Initial implementation
 5938%;
 5939%; @book{Mueller:2006,
 5940%;   author = "Erik T. Mueller",
 5941%;   year = "2006",
 5942%;   title = "Commonsense Reasoning",
 5943%;   address = "San Francisco",
 5944%;   publisher = "Morgan Kaufmann/Elsevier",
 5945%; }
 5946%;
 5947
 5948% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1747
 5949% load foundations/Root.e
 5950
 5951% load foundations/EC.e
 5952
 5953% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1750
 5954% sort agent
 5955% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1751
 5956==> sort(agent).
 5957
 5958% event PatHead(agent)
 5959 %  event(patHead(agent)).
 5960% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1753
 5961==> mpred_prop(patHead(agent),event).
 5962==> meta_argtypes(patHead(agent)).
 5963
 5964% event RubStomach(agent)
 5965 %  event(rubStomach(agent)).
 5966% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1754
 5967==> mpred_prop(rubStomach(agent),event).
 5968==> meta_argtypes(rubStomach(agent)).
 5969
 5970% agent Nathan
 5971% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1756
 5972==> t(agent,nathan).
 5973%; Delta
 5974% [agent,time]
 5975% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1760
 5976% Happens(PatHead(agent),time) ->
 5977% !Happens(RubStomach(agent),time).
 5978% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1761
 5979axiom(not(happens(rubStomach(Agent), Time)),
 5980    [happens(patHead(Agent), Time)]).
 5981
 5982
 5983% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1763
 5984% Happens(PatHead(Nathan),0) & Happens(RubStomach(Nathan),0).
 5985
 5986 /*   happens(patHead(nathan), 0),
 5987      happens(rubStomach(nathan), 0).
 5988 */
 5989axiom(happens(patHead(nathan), t),
 5990    [is_time(0)]).
 5991axiom(happens(rubStomach(nathan), t),
 5992    [is_time(0)]).
 5993
 5994% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1765
 5995% range time 0 1
 5996% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1766
 5997==> range(time,0,1).
 5998
 5999% range offset 1 1
 6000% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1767
 6001==> range(offset,1,1).
 6002%; End of file.
 6003%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 6004%; FILE: examples/Mueller2006/Chapter10/MovingNewspaperAndBox.e
 6005%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 6006%;
 6007%; Copyright (c) 2005 IBM Corporation and others.
 6008%; All rights reserved. This program and the accompanying materials
 6009%; are made available under the terms of the Common Public License v1.0
 6010%; which accompanies this distribution, and is available at
 6011%; http://www.eclipse.org/legal/cpl-v10.html
 6012%;
 6013%; Contributors:
 6014%; IBM - Initial implementation
 6015%;
 6016%; @book{Mueller:2006,
 6017%;   author = "Erik T. Mueller",
 6018%;   year = "2006",
 6019%;   title = "Commonsense Reasoning",
 6020%;   address = "San Francisco",
 6021%;   publisher = "Morgan Kaufmann/Elsevier",
 6022%; }
 6023%;
 6024
 6025% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1794
 6026% load foundations/Root.e
 6027
 6028% load foundations/EC.e
 6029
 6030% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1797
 6031% sort object
 6032% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1798
 6033==> sort(object).
 6034
 6035% sort agent: object
 6036% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1799
 6037==> subsort(agent,object).
 6038
 6039% sort physobj: object
 6040% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1800
 6041==> subsort(physobj,object).
 6042
 6043% sort room: object
 6044% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1801
 6045==> subsort(room,object).
 6046
 6047% fluent IN(object,object)
 6048 %  fluent(in(object,object)).
 6049% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1803
 6050==> mpred_prop(in(object,object),fluent).
 6051==> meta_argtypes(in(object,object)).
 6052
 6053% fluent INROOM(object,room)
 6054 %  fluent(inroom(object,room)).
 6055% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1804
 6056==> mpred_prop(inroom(object,room),fluent).
 6057==> meta_argtypes(inroom(object,room)).
 6058
 6059% noninertial INROOM
 6060% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1805
 6061==> noninertial(inroom).
 6062
 6063% event MOVE(agent,object,object,object)
 6064 %  event(move(agent,object,object,object)).
 6065% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1807
 6066==> mpred_prop(move(agent,object,object,object),event).
 6067==> meta_argtypes(move(agent,object,object,object)).
 6068
 6069% agent Lisa
 6070% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1809
 6071==> t(agent,lisa).
 6072
 6073% physobj Box, Newspaper
 6074% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1810
 6075==> t(physobj,box).
 6076==> t(physobj,newspaper).
 6077
 6078% room Kitchen, LivingRoom
 6079% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1811
 6080==> t(room,kitchen).
 6081==> t(room,livingRoom).
 6082%; Sigma
 6083%; RS10
 6084% [agent,physobj1,physobj2,room,time]
 6085% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1816
 6086% HoldsAt(IN(agent,room),time) &
 6087% HoldsAt(IN(physobj1,room),time) &
 6088% HoldsAt(INROOM(physobj2,room),time) ->
 6089% Initiates(MOVE(agent,physobj1,room,physobj2),IN(physobj1,physobj2),time).
 6090% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1819
 6091axiom(initiates(move(Agent, Physobj1, Room, Physobj2), in(Physobj1, Physobj2), Time),
 6092   
 6093    [ holds_at(in(Agent, Room), Time),
 6094      holds_at(in(Physobj1, Room), Time),
 6095      holds_at(inroom(Physobj2, Room), Time)
 6096    ]).
 6097
 6098
 6099% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1821
 6100%; RS11
 6101% [agent,physobj1,physobj2,room,time]
 6102% HoldsAt(IN(agent,room),time) &
 6103% HoldsAt(IN(physobj1,room),time) &
 6104% HoldsAt(INROOM(physobj2,room),time) ->
 6105% Terminates(MOVE(agent,physobj1,room,physobj2),IN(physobj1,room),time).
 6106% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1826
 6107axiom(terminates(move(Agent, Physobj1, Room, Physobj2), in(Physobj1, Room), Time),
 6108   
 6109    [ holds_at(in(Agent, Room), Time),
 6110      holds_at(in(Physobj1, Room), Time),
 6111      holds_at(inroom(Physobj2, Room), Time)
 6112    ]).
 6113
 6114
 6115% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1828
 6116%; RS12
 6117% [agent,physobj1,physobj2,room,time]
 6118% HoldsAt(IN(agent,room),time) ->
 6119% Initiates(MOVE(agent,physobj1,physobj2,room),IN(physobj1,room),time).
 6120% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1831
 6121axiom(initiates(move(Agent, Physobj1, Physobj2, Room), in(Physobj1, Room), Time),
 6122    [holds_at(in(Agent, Room), Time)]).
 6123
 6124
 6125% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1833
 6126%; RS13
 6127% [agent,physobj1,physobj2,room,time]
 6128% HoldsAt(IN(agent,room),time) ->
 6129% Terminates(MOVE(agent,physobj1,physobj2,room),IN(physobj1,physobj2),time).
 6130% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1836
 6131axiom(terminates(move(Agent, Physobj1, Physobj2, Room), in(Physobj1, Physobj2), Time),
 6132    [holds_at(in(Agent, Room), Time)]).
 6133
 6134
 6135% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1838
 6136%; RS14
 6137% [agent,room1,room2,time]
 6138% HoldsAt(IN(agent,room1),time) ->
 6139% Initiates(MOVE(agent,agent,room1,room2),IN(agent,room2),time).
 6140% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1841
 6141axiom(initiates(move(Agent, Agent, Room1, Room2), in(Agent, Room2), Time),
 6142    [holds_at(in(Agent, Room1), Time)]).
 6143
 6144
 6145% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1843
 6146%; RS15
 6147% [agent,room1,room2,time]
 6148% HoldsAt(IN(agent,room1),time) ->
 6149% Terminates(MOVE(agent,agent,room1,room2),IN(agent,room1),time).
 6150% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1846
 6151axiom(terminates(move(Agent, Agent, Room1, Room2), in(Agent, Room1), Time),
 6152    [holds_at(in(Agent, Room1), Time)]).
 6153
 6154
 6155% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1848
 6156%; RS16
 6157% [agent,physobj,room,time]
 6158% HoldsAt(IN(agent,room),time) &
 6159% HoldsAt(IN(physobj,room),time) ->
 6160% Initiates(MOVE(agent,physobj,room,agent),IN(physobj,agent),time).
 6161% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1852
 6162axiom(initiates(move(Agent, Physobj, Room, Agent), in(Physobj, Agent), Time),
 6163   
 6164    [ holds_at(in(Agent, Room), Time),
 6165      holds_at(in(Physobj, Room), Time)
 6166    ]).
 6167
 6168
 6169% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1854
 6170%; RS17
 6171% [agent,physobj,room,time]
 6172% HoldsAt(IN(agent,room),time) &
 6173% HoldsAt(IN(physobj,room),time) ->
 6174% Terminates(MOVE(agent,physobj,room,agent),IN(physobj,room),time).
 6175% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1858
 6176axiom(terminates(move(Agent, Physobj, Room, Agent), in(Physobj, Room), Time),
 6177   
 6178    [ holds_at(in(Agent, Room), Time),
 6179      holds_at(in(Physobj, Room), Time)
 6180    ]).
 6181
 6182
 6183% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1860
 6184%; RS18
 6185% [agent,physobj,room,time]
 6186% HoldsAt(IN(physobj,agent),time) &
 6187% HoldsAt(IN(agent,room),time) ->
 6188% Initiates(MOVE(agent,physobj,agent,room),IN(physobj,room),time).
 6189% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1864
 6190axiom(initiates(move(Agent, Physobj, Agent, Room), in(Physobj, Room), Time),
 6191   
 6192    [ holds_at(in(Physobj, Agent), Time),
 6193      holds_at(in(Agent, Room), Time)
 6194    ]).
 6195
 6196
 6197% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1866
 6198%; RS19
 6199% [agent,physobj,room,time]
 6200% HoldsAt(IN(physobj,agent),time) &
 6201% HoldsAt(IN(agent,room),time) ->
 6202% Terminates(MOVE(agent,physobj,agent,room),IN(physobj,agent),time).
 6203% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1870
 6204axiom(terminates(move(Agent, Physobj, Agent, Room), in(Physobj, Agent), Time),
 6205   
 6206    [ holds_at(in(Physobj, Agent), Time),
 6207      holds_at(in(Agent, Room), Time)
 6208    ]).
 6209
 6210
 6211% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1872
 6212%; Delta
 6213
 6214
 6215% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1874
 6216% Happens(MOVE(Lisa,Newspaper,LivingRoom,Box),0).
 6217axiom(happens(move(lisa, newspaper, livingRoom, box), t),
 6218    [is_time(0)]).
 6219
 6220
 6221% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1875
 6222% Happens(MOVE(Lisa,Box,LivingRoom,Lisa),1).
 6223axiom(happens(move(lisa, box, livingRoom, lisa), start),
 6224    [is_time(1), b(t, start), ignore(t+1=start)]).
 6225
 6226
 6227% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1876
 6228% Happens(MOVE(Lisa,Lisa,LivingRoom,Kitchen),2).
 6229axiom(happens(move(lisa, lisa, livingRoom, kitchen), t2),
 6230    [is_time(2), b(t, t2), ignore(t+2=t2)]).
 6231
 6232
 6233% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1877
 6234% Happens(MOVE(Lisa,Box,Lisa,Kitchen),3).
 6235axiom(happens(move(lisa, box, lisa, kitchen), t3),
 6236    [is_time(3), b(t, t3), ignore(t+3=t3)]).
 6237
 6238
 6239% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1878
 6240% Happens(MOVE(Lisa,Lisa,Kitchen,LivingRoom),4).
 6241axiom(happens(move(lisa, lisa, kitchen, livingRoom), t4),
 6242    [is_time(4), b(t, t4), ignore(t+4=t4)]).
 6243
 6244
 6245% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1880
 6246%; Psi
 6247%; RS1
 6248% [object,time]
 6249 
 6250% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1883
 6251% !HoldsAt(IN(object,object),time).
 6252 %  not(holds_at(in(Object,Object),Time)).
 6253axiom(not(holds_at(in(In_Param, In_Param), Time2)),
 6254    []).
 6255
 6256
 6257% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1885
 6258%; RS2
 6259% [object1,object2,time]
 6260% HoldsAt(IN(object1,object2),time) ->
 6261% !HoldsAt(IN(object2,object1),time).
 6262% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1888
 6263axiom(not(holds_at(in(Object2, Object1), Time)),
 6264    [holds_at(in(Object1, Object2), Time)]).
 6265
 6266
 6267% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1890
 6268%; RS3
 6269% [object1,object2,object3,time]
 6270% HoldsAt(IN(object1,object2),time) &
 6271% HoldsAt(IN(object2,object3),time) ->
 6272% !HoldsAt(IN(object1,object3),time).
 6273% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1894
 6274axiom(not(holds_at(in(Object1, Object3), Time)),
 6275   
 6276    [ holds_at(in(Object1, Object2), Time),
 6277      holds_at(in(Object2, Object3), Time)
 6278    ]).
 6279
 6280
 6281% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1896
 6282%; RS4
 6283% [object,object1,object2,time]
 6284% HoldsAt(IN(object,object1),time) &
 6285% HoldsAt(IN(object,object2),time) ->
 6286% object1=object2.
 6287% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1900
 6288axiom(Object1=Object2,
 6289   
 6290    [ holds_at(in(Object, Object1), Time),
 6291      holds_at(in(Object, Object2), Time)
 6292    ]).
 6293
 6294
 6295% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1902
 6296%; RS7
 6297% [object,room,time]
 6298% HoldsAt(IN(object,room),time) ->
 6299% HoldsAt(INROOM(object,room),time).
 6300% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1905
 6301axiom(holds_at(inroom(Object, Room), Time),
 6302    [holds_at(in(Object, Room), Time)]).
 6303
 6304
 6305% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1907
 6306%; RS8
 6307% [object1,object2,room,time]
 6308% HoldsAt(IN(object1,object2),time) &
 6309% HoldsAt(INROOM(object2,room),time) ->
 6310% HoldsAt(INROOM(object1,room),time).
 6311% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1911
 6312axiom(holds_at(inroom(Object1, Room), Time),
 6313   
 6314    [ holds_at(in(Object1, Object2), Time),
 6315      holds_at(inroom(Object2, Room), Time)
 6316    ]).
 6317
 6318
 6319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1913
 6320%; RS9
 6321% [object,room1,room2,time]
 6322% HoldsAt(INROOM(object,room1),time) &
 6323% HoldsAt(INROOM(object,room2),time) ->
 6324% room1=room2.
 6325% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1917
 6326axiom(Room1=Room2,
 6327   
 6328    [ holds_at(inroom(Object, Room1), Time),
 6329      holds_at(inroom(Object, Room2), Time)
 6330    ]).
 6331
 6332
 6333% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1919
 6334%; Gamma
 6335
 6336
 6337% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1921
 6338% HoldsAt(IN(Lisa,LivingRoom),0).
 6339axiom(initially(in(lisa, livingRoom)),
 6340    []).
 6341
 6342
 6343% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1922
 6344% HoldsAt(IN(Newspaper,LivingRoom),0).
 6345axiom(initially(in(newspaper, livingRoom)),
 6346    []).
 6347
 6348
 6349% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1923
 6350% HoldsAt(IN(Box,LivingRoom),0).
 6351axiom(initially(in(box, livingRoom)),
 6352    []).
 6353
 6354
 6355% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1925
 6356%; added:
 6357% [room1,room2,time]
 6358 % !HoldsAt(INROOM(room1,room2),time).
 6359 %  not(holds_at(inroom(Room1,Room2),Time)).
 6360% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1926
 6361axiom(not(holds_at(inroom(Inroom_Param, Inroom_Ret), Time3)),
 6362    []).
 6363
 6364
 6365% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1927
 6366% [room,object,time]
 6367 % !HoldsAt(IN(room,object),time).
 6368 %  not(holds_at(in(Room,Object),Time)).
 6369axiom(not(holds_at(in(In_Param, In_Ret), Time3)),
 6370    []).
 6371
 6372
 6373% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1929
 6374%; entailed:
 6375%; HoldsAt(IN(Lisa,LivingRoom),5).
 6376%; HoldsAt(IN(Box,Kitchen),5).
 6377%; HoldsAt(INROOM(Newspaper,Kitchen),5).
 6378
 6379% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1934
 6380% completion Happens
 6381% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1935
 6382==> completion(happens).
 6383
 6384% range time 0 5
 6385% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1937
 6386==> range(time,0,5).
 6387
 6388% range offset 1 1
 6389% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1938
 6390==> range(offset,1,1).
 6391%; End of file.
 6392%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 6393%; FILE: examples/Mueller2006/Chapter10/TwoScreens.e
 6394%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 6395%;
 6396%; Copyright (c) 2005 IBM Corporation and others.
 6397%; All rights reserved. This program and the accompanying materials
 6398%; are made available under the terms of the Common Public License v1.0
 6399%; which accompanies this distribution, and is available at
 6400%; http://www.eclipse.org/legal/cpl-v10.html
 6401%;
 6402%; Contributors:
 6403%; IBM - Initial implementation
 6404%;
 6405%; @phdthesis{Cassimatis:2002,
 6406%;   author = "Nicholas L. Cassimatis",
 6407%;   year = "2002",
 6408%;   title = "Polyscheme: A Cognitive Architecture for Integrating Multiple Representation and Inference Schemes",
 6409%;   address = "Cambridge, MA",
 6410%;   school = "Program in Media Arts and Sciences, School of Architecture and Planning, Massachusetts Institute of Technology",
 6411%; }
 6412%;
 6413%; @book{Mueller:2006,
 6414%;   author = "Erik T. Mueller",
 6415%;   year = "2006",
 6416%;   title = "Commonsense Reasoning",
 6417%;   address = "San Francisco",
 6418%;   publisher = "Morgan Kaufmann/Elsevier",
 6419%; }
 6420%;
 6421
 6422% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1973
 6423% load foundations/Root.e
 6424
 6425% load foundations/EC.e
 6426
 6427% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1976
 6428% sort object
 6429% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1977
 6430==> sort(object).
 6431
 6432% sort location
 6433% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1978
 6434==> sort(location).
 6435
 6436% object O1, O2
 6437% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1980
 6438==> t(object,o1).
 6439==> t(object,o2).
 6440
 6441% location L1, L2, L3, L4, L5
 6442% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1981
 6443==> t(location,l1).
 6444==> t(location,l2).
 6445==> t(location,l3).
 6446==> t(location,l4).
 6447==> t(location,l5).
 6448
 6449% predicate Adjacent(location,location)
 6450 %  predicate(adjacent(location,location)).
 6451% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1983
 6452==> mpred_prop(adjacent(location,location),predicate).
 6453==> meta_argtypes(adjacent(location,location)).
 6454
 6455% predicate Equal(object,object)
 6456 %  predicate(equal(object,object)).
 6457% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1984
 6458==> mpred_prop(equal(object,object),predicate).
 6459==> meta_argtypes(equal(object,object)).
 6460
 6461% fluent At(object,location)
 6462 %  fluent(at(object,location)).
 6463% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1986
 6464==> mpred_prop(at(object,location),fluent).
 6465==> meta_argtypes(at(object,location)).
 6466
 6467% event Move(object,location,location)
 6468 %  event(move(object,location,location)).
 6469% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1987
 6470==> mpred_prop(move(object,location,location),event).
 6471==> meta_argtypes(move(object,location,location)).
 6472
 6473
 6474% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1988
 6475%; Sigma
 6476% [object,location1,location2,time]
 6477% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1991
 6478% HoldsAt(At(object,location1),time) &
 6479% Adjacent(location1,location2) ->
 6480% Initiates(Move(object,location1,location2),At(object,location2),time).
 6481% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1993
 6482axiom(initiates(move(Object, Location1, Location2), at(Object, Location2), Time),
 6483   
 6484    [ holds_at(at(Object, Location1), Time),
 6485      adjacent(Location1, Location2)
 6486    ]).
 6487
 6488
 6489% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1995
 6490% [object,location1,location2,time]
 6491% HoldsAt(At(object,location1),time) &
 6492% Adjacent(location1,location2) ->
 6493% Terminates(Move(object,location1,location2),At(object,location1),time).
 6494% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:1998
 6495axiom(terminates(move(Object, Location1, Location2), at(Object, Location1), Time),
 6496   
 6497    [ holds_at(at(Object, Location1), Time),
 6498      adjacent(Location1, Location2)
 6499    ]).
 6500
 6501
 6502% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2000
 6503%; Psi
 6504% [object,location1,location2,time]
 6505% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2003
 6506% HoldsAt(At(object,location1),time) &
 6507% HoldsAt(At(object,location2),time) ->
 6508% location1=location2.
 6509% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2005
 6510axiom(Location1=Location2,
 6511   
 6512    [ holds_at(at(Object, Location1), Time),
 6513      holds_at(at(Object, Location2), Time)
 6514    ]).
 6515
 6516
 6517% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2007
 6518% [object,time]
 6519% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2008
 6520% {location} % HoldsAt(At(object,location),time).
 6521
 6522 /*  exists([Location],
 6523          holds_at(at(Object,Location),Time)).
 6524 */
 6525
 6526 /*  holds_at(at(At_Param, Location4), Time5) :-
 6527       some(Location4, '$kolem_Fn_351'(At_Param, Time5)).
 6528 */
 6529axiom(holds_at(at(At_Param, Location4), Time5),
 6530    [some(Location4, '$kolem_Fn_351'(At_Param, Time5))]).
 6531
 6532 /*  not(some(Location7, '$kolem_Fn_351'(Fn_351_Param, Time8))) :-
 6533       not(holds_at(at(Fn_351_Param, Location7), Time8)).
 6534 */
 6535axiom(not(some(Location7, '$kolem_Fn_351'(Fn_351_Param, Time8))),
 6536    [not(holds_at(at(Fn_351_Param, Location7), Time8))]).
 6537
 6538
 6539% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2010
 6540% [object1,object2,location,time]
 6541% HoldsAt(At(object1,location),time) &
 6542% HoldsAt(At(object2,location),time) ->
 6543% Equal(object1,object2).
 6544% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2013
 6545axiom(equal(Object1, Object2),
 6546   
 6547    [ holds_at(at(Object1, Location), Time),
 6548      holds_at(at(Object2, Location), Time)
 6549    ]).
 6550
 6551
 6552% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2015
 6553% [location1, location2]
 6554% Adjacent(location1,location2) <->
 6555% Adjacent(location2,location1).
 6556
 6557 /*  adjacent(Location1, Location2) <->
 6558       adjacent(Location2, Location1).
 6559 */
 6560% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2017
 6561axiom(adjacent(Location1, Location2),
 6562    [adjacent(Location2, Location1)]).
 6563axiom(adjacent(Location2, Location1),
 6564    [adjacent(Location1, Location2)]).
 6565
 6566
 6567% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2019
 6568% [object1,object2]
 6569% Equal(object1,object2) <->
 6570% Equal(object2,object1).
 6571
 6572 /*  equal(Object1, Object2) <->
 6573       equal(Object2, Object1).
 6574 */
 6575% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2021
 6576axiom(equal(Object1, Object2),
 6577    [equal(Object2, Object1)]).
 6578axiom(equal(Object2, Object1),
 6579    [equal(Object1, Object2)]).
 6580
 6581
 6582% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2023
 6583%; Gamma
 6584% [location1,location2]
 6585% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2026
 6586% Adjacent(location1,location2) <->
 6587% (location1=L1 & location2=L2) |
 6588% (location1=L2 & location2=L1) |
 6589% (location1=L2 & location2=L3) |
 6590% (location1=L3 & location2=L2) |
 6591% (location1=L3 & location2=L4) |
 6592% (location1=L4 & location2=L3) |
 6593% (location1=L4 & location2=L5) |
 6594% (location1=L5 & location2=L4).
 6595
 6596 /*  adjacent(Location1, Location2) <->
 6597       (   Location1=l1,
 6598           Location2=l2
 6599       ;   Location1=l2,
 6600           Location2=l1
 6601       ;   Location1=l2,
 6602           Location2=l3
 6603       ;   Location1=l3,
 6604           Location2=l2
 6605       ;   Location1=l3,
 6606           Location2=l4
 6607       ;   Location1=l4,
 6608           Location2=l3
 6609       ;   Location1=l4,
 6610           Location2=l5
 6611       ;   Location1=l5,
 6612           Location2=l4
 6613       ).
 6614 */
 6615% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2034
 6616axiom(adjacent(Location1, Location2),
 6617    [equals(Location1, l1), equals(Location2, l2)]).
 6618axiom(adjacent(Location1, Location2),
 6619    [equals(Location1, l2), equals(Location2, l1)]).
 6620axiom(adjacent(Location1, Location2),
 6621    [equals(Location1, l2), equals(Location2, l3)]).
 6622axiom(adjacent(Location1, Location2),
 6623    [equals(Location1, l3), equals(Location2, l2)]).
 6624axiom(adjacent(Location1, Location2),
 6625    [equals(Location1, l3), equals(Location2, l4)]).
 6626axiom(adjacent(Location1, Location2),
 6627    [equals(Location1, l4), equals(Location2, l3)]).
 6628axiom(adjacent(Location1, Location2),
 6629    [equals(Location1, l4), equals(Location2, l5)]).
 6630axiom(adjacent(Location1, Location2),
 6631    [equals(Location1, l5), equals(Location2, l4)]).
 6632
 6633 /*   if(adjacent(Location1, Location2),
 6634          (Location1=l1, Location2=l2;Location1=l2, Location2=l1;Location1=l2, Location2=l3;Location1=l3, Location2=l2;Location1=l3, Location2=l4;Location1=l4, Location2=l3;Location1=l4, Location2=l5;Location1=l5, Location2=l4)).
 6635 */
 6636todo_later(if(adjacent(Location1, Location2),  (Location1=l1, Location2=l2;Location1=l2, Location2=l1;Location1=l2, Location2=l3;Location1=l3, Location2=l2;Location1=l3, Location2=l4;Location1=l4, Location2=l3;Location1=l4, Location2=l5;Location1=l5, Location2=l4)), [(not(adjacent(Adjacent_Param, Equals_Param)):-(not(equals(Adjacent_Param, l1));not(equals(Equals_Param, l2))), (not(equals(Adjacent_Param, l2));not(equals(Equals_Param, l1))), (not(equals(Adjacent_Param, l2));not(equals(Equals_Param, l3))), (not(equals(Adjacent_Param, l3));not(equals(Equals_Param, l2))), (not(equals(Adjacent_Param, l3));not(equals(Equals_Param, l4))), (not(equals(Adjacent_Param, l4));not(equals(Equals_Param, l3))), (not(equals(Adjacent_Param, l4));not(equals(Equals_Param, l5))), (not(equals(Adjacent_Param, l5));not(equals(Equals_Param, l4)))),  (equals(Equals_Param4, l1):-((not(equals(Equals_Param4, l2));not(equals(Equals_Param5, l1))), (not(equals(Equals_Param4, l2));not(equals(Equals_Param5, l3))), (not(equals(Equals_Param4, l3));not(equals(Equals_Param5, l2))), (not(equals(Equals_Param4, l3));not(equals(Equals_Param5, l4))), (not(equals(Equals_Param4, l4));not(equals(Equals_Param5, l3))), (not(equals(Equals_Param4, l4));not(equals(Equals_Param5, l5))), (not(equals(Equals_Param4, l5));not(equals(Equals_Param5, l4)))), adjacent(Equals_Param4, Equals_Param5)),  (equals(Equals_Param6, l2):-((not(equals(Equals_Param7, l2));not(equals(Equals_Param6, l1))), (not(equals(Equals_Param7, l2));not(equals(Equals_Param6, l3))), (not(equals(Equals_Param7, l3));not(equals(Equals_Param6, l2))), (not(equals(Equals_Param7, l3));not(equals(Equals_Param6, l4))), (not(equals(Equals_Param7, l4));not(equals(Equals_Param6, l3))), (not(equals(Equals_Param7, l4));not(equals(Equals_Param6, l5))), (not(equals(Equals_Param7, l5));not(equals(Equals_Param6, l4)))), adjacent(Equals_Param7, Equals_Param6)),  (equals(Equals_Param8, l2):-((not(equals(Equals_Param8, l2));not(equals(Equals_Param9, l3))), (not(equals(Equals_Param8, l3));not(equals(Equals_Param9, l2))), (not(equals(Equals_Param8, l3));not(equals(Equals_Param9, l4))), (not(equals(Equals_Param8, l4));not(equals(Equals_Param9, l3))), (not(equals(Equals_Param8, l4));not(equals(Equals_Param9, l5))), (not(equals(Equals_Param8, l5));not(equals(Equals_Param9, l4)))), (not(equals(Equals_Param8, l1));not(equals(Equals_Param9, l2))), adjacent(Equals_Param8, Equals_Param9)),  (equals(Equals_Param10, l1):-((not(equals(Equals_Param11, l2));not(equals(Equals_Param10, l3))), (not(equals(Equals_Param11, l3));not(equals(Equals_Param10, l2))), (not(equals(Equals_Param11, l3));not(equals(Equals_Param10, l4))), (not(equals(Equals_Param11, l4));not(equals(Equals_Param10, l3))), (not(equals(Equals_Param11, l4));not(equals(Equals_Param10, l5))), (not(equals(Equals_Param11, l5));not(equals(Equals_Param10, l4)))), (not(equals(Equals_Param11, l1));not(equals(Equals_Param10, l2))), adjacent(Equals_Param11, Equals_Param10)),  (equals(Equals_Param12, l2):-((not(equals(Equals_Param12, l3));not(equals(Equals_Param13, l2))), (not(equals(Equals_Param12, l3));not(equals(Equals_Param13, l4))), (not(equals(Equals_Param12, l4));not(equals(Equals_Param13, l3))), (not(equals(Equals_Param12, l4));not(equals(Equals_Param13, l5))), (not(equals(Equals_Param12, l5));not(equals(Equals_Param13, l4)))), (not(equals(Equals_Param12, l2));not(equals(Equals_Param13, l1))), (not(equals(Equals_Param12, l1));not(equals(Equals_Param13, l2))), adjacent(Equals_Param12, Equals_Param13)),  (equals(Equals_Param14, l3):-((not(equals(Equals_Param15, l3));not(equals(Equals_Param14, l2))), (not(equals(Equals_Param15, l3));not(equals(Equals_Param14, l4))), (not(equals(Equals_Param15, l4));not(equals(Equals_Param14, l3))), (not(equals(Equals_Param15, l4));not(equals(Equals_Param14, l5))), (not(equals(Equals_Param15, l5));not(equals(Equals_Param14, l4)))), (not(equals(Equals_Param15, l2));not(equals(Equals_Param14, l1))), (not(equals(Equals_Param15, l1));not(equals(Equals_Param14, l2))), adjacent(Equals_Param15, Equals_Param14)),  (equals(Equals_Param16, l3):-((not(equals(Equals_Param16, l3));not(equals(Equals_Param17, l4))), (not(equals(Equals_Param16, l4));not(equals(Equals_Param17, l3))), (not(equals(Equals_Param16, l4));not(equals(Equals_Param17, l5))), (not(equals(Equals_Param16, l5));not(equals(Equals_Param17, l4)))), (not(equals(Equals_Param16, l2));not(equals(Equals_Param17, l3))), (not(equals(Equals_Param16, l2));not(equals(Equals_Param17, l1))), (not(equals(Equals_Param16, l1));not(equals(Equals_Param17, l2))), adjacent(Equals_Param16, Equals_Param17)),  (equals(Equals_Param18, l2):-((not(equals(Equals_Param19, l3));not(equals(Equals_Param18, l4))), (not(equals(Equals_Param19, l4));not(equals(Equals_Param18, l3))), (not(equals(Equals_Param19, l4));not(equals(Equals_Param18, l5))), (not(equals(Equals_Param19, l5));not(equals(Equals_Param18, l4)))), (not(equals(Equals_Param19, l2));not(equals(Equals_Param18, l3))), (not(equals(Equals_Param19, l2));not(equals(Equals_Param18, l1))), (not(equals(Equals_Param19, l1));not(equals(Equals_Param18, l2))), adjacent(Equals_Param19, Equals_Param18)),  (equals(Equals_Param20, l3):-((not(equals(Equals_Param20, l4));not(equals(Equals_Param21, l3))), (not(equals(Equals_Param20, l4));not(equals(Equals_Param21, l5))), (not(equals(Equals_Param20, l5));not(equals(Equals_Param21, l4)))), (not(equals(Equals_Param20, l3));not(equals(Equals_Param21, l2))), (not(equals(Equals_Param20, l2));not(equals(Equals_Param21, l3))), (not(equals(Equals_Param20, l2));not(equals(Equals_Param21, l1))), (not(equals(Equals_Param20, l1));not(equals(Equals_Param21, l2))), adjacent(Equals_Param20, Equals_Param21)),  (equals(Equals_Param22, l4):-((not(equals(Equals_Param23, l4));not(equals(Equals_Param22, l3))), (not(equals(Equals_Param23, l4));not(equals(Equals_Param22, l5))), (not(equals(Equals_Param23, l5));not(equals(Equals_Param22, l4)))), (not(equals(Equals_Param23, l3));not(equals(Equals_Param22, l2))), (not(equals(Equals_Param23, l2));not(equals(Equals_Param22, l3))), (not(equals(Equals_Param23, l2));not(equals(Equals_Param22, l1))), (not(equals(Equals_Param23, l1));not(equals(Equals_Param22, l2))), adjacent(Equals_Param23, Equals_Param22)),  (equals(Equals_Param24, l4):-((not(equals(Equals_Param24, l4));not(equals(Equals_Param25, l5))), (not(equals(Equals_Param24, l5));not(equals(Equals_Param25, l4)))), (not(equals(Equals_Param24, l3));not(equals(Equals_Param25, l4))), (not(equals(Equals_Param24, l3));not(equals(Equals_Param25, l2))), (not(equals(Equals_Param24, l2));not(equals(Equals_Param25, l3))), (not(equals(Equals_Param24, l2));not(equals(Equals_Param25, l1))), (not(equals(Equals_Param24, l1));not(equals(Equals_Param25, l2))), adjacent(Equals_Param24, Equals_Param25)),  (equals(Equals_Param26, l3):-((not(equals(Equals_Param27, l4));not(equals(Equals_Param26, l5))), (not(equals(Equals_Param27, l5));not(equals(Equals_Param26, l4)))), (not(equals(Equals_Param27, l3));not(equals(Equals_Param26, l4))), (not(equals(Equals_Param27, l3));not(equals(Equals_Param26, l2))), (not(equals(Equals_Param27, l2));not(equals(Equals_Param26, l3))), (not(equals(Equals_Param27, l2));not(equals(Equals_Param26, l1))), (not(equals(Equals_Param27, l1));not(equals(Equals_Param26, l2))), adjacent(Equals_Param27, Equals_Param26)),  (equals(Equals_Param28, l4):-(not(equals(Equals_Param28, l5));not(equals(Equals_Param29, l4))), (not(equals(Equals_Param28, l4));not(equals(Equals_Param29, l3))), (not(equals(Equals_Param28, l3));not(equals(Equals_Param29, l4))), (not(equals(Equals_Param28, l3));not(equals(Equals_Param29, l2))), (not(equals(Equals_Param28, l2));not(equals(Equals_Param29, l3))), (not(equals(Equals_Param28, l2));not(equals(Equals_Param29, l1))), (not(equals(Equals_Param28, l1));not(equals(Equals_Param29, l2))), adjacent(Equals_Param28, Equals_Param29)),  (equals(Equals_Param30, l5):-(not(equals(Equals_Param31, l5));not(equals(Equals_Param30, l4))), (not(equals(Equals_Param31, l4));not(equals(Equals_Param30, l3))), (not(equals(Equals_Param31, l3));not(equals(Equals_Param30, l4))), (not(equals(Equals_Param31, l3));not(equals(Equals_Param30, l2))), (not(equals(Equals_Param31, l2));not(equals(Equals_Param30, l3))), (not(equals(Equals_Param31, l2));not(equals(Equals_Param30, l1))), (not(equals(Equals_Param31, l1));not(equals(Equals_Param30, l2))), adjacent(Equals_Param31, Equals_Param30)),  (equals(Equals_Param32, l5):-(not(equals(Equals_Param32, l4));not(equals(Equals_Param33, l5))), (not(equals(Equals_Param32, l4));not(equals(Equals_Param33, l3))), (not(equals(Equals_Param32, l3));not(equals(Equals_Param33, l4))), (not(equals(Equals_Param32, l3));not(equals(Equals_Param33, l2))), (not(equals(Equals_Param32, l2));not(equals(Equals_Param33, l3))), (not(equals(Equals_Param32, l2));not(equals(Equals_Param33, l1))), (not(equals(Equals_Param32, l1));not(equals(Equals_Param33, l2))), adjacent(Equals_Param32, Equals_Param33)),  (equals(Equals_Param34, l4):-(not(equals(Equals_Param35, l4));not(equals(Equals_Param34, l5))), (not(equals(Equals_Param35, l4));not(equals(Equals_Param34, l3))), (not(equals(Equals_Param35, l3));not(equals(Equals_Param34, l4))), (not(equals(Equals_Param35, l3));not(equals(Equals_Param34, l2))), (not(equals(Equals_Param35, l2));not(equals(Equals_Param34, l3))), (not(equals(Equals_Param35, l2));not(equals(Equals_Param34, l1))), (not(equals(Equals_Param35, l1));not(equals(Equals_Param34, l2))), adjacent(Equals_Param35, Equals_Param34))], 17==17).
 6637
 6638
 6639% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2036
 6640% HoldsAt(At(O1,L1),0).
 6641axiom(initially(at(o1, l1)),
 6642    []).
 6643
 6644
 6645% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2037
 6646% [object]
 6647 % !HoldsAt(At(object,L5),0).
 6648 %  not(initially(at(Object,l5))).
 6649axiom(not(initially(at(At_Param, l5))),
 6650    []).
 6651
 6652
 6653% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2039
 6654% HoldsAt(At(O2,L5),4).
 6655holds_at(at(o2,l5),4).
 6656
 6657
 6658% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2040
 6659% [object]
 6660 % !HoldsAt(At(object,L1),4).
 6661 %  not(holds_at(at(Object,l1),4)).
 6662axiom(not(holds_at(at(At_Param, l1), t4)),
 6663    [b(t, t4), ignore(t+4=t4)]).
 6664
 6665
 6666% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2042
 6667% [object,time]
 6668 % !HoldsAt(At(object,L3),time).
 6669 %  not(holds_at(at(Object,l3),Time)).
 6670axiom(not(holds_at(at(At_Param, l3), Time2)),
 6671    []).
 6672
 6673
 6674% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2044
 6675%; ADDED:
 6676% [object,location1,location2,time]
 6677% Happens(Move(object,location1,location2),time) ->
 6678% HoldsAt(At(object,location1),time) &
 6679% Adjacent(location1,location2).
 6680% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2048
 6681axiom(requires(move(Object, Location1, Location2), Time),
 6682   
 6683    [ holds_at(at(Object, Location1), Time),
 6684      adjacent(Location1, Location2)
 6685    ]).
 6686
 6687
 6688% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2050
 6689% [object1,object2,location1,location2,time]
 6690% Equal(object1,object2) &
 6691% Happens(Move(object1,location1,location2),time) ->
 6692% Happens(Move(object2,location1,location2),time).
 6693% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2053
 6694axiom(happens(move(Object2, Location1, Location2), Time),
 6695   
 6696    [ equal(Object1, Object2),
 6697      happens(move(Object1, Location1, Location2), Time)
 6698    ]).
 6699
 6700
 6701% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2055
 6702%; entailed: !Equal(O1,O2).
 6703
 6704% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2057
 6705% range time 0 4
 6706% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2058
 6707==> range(time,0,4).
 6708
 6709% range offset 1 1
 6710% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2059
 6711==> range(offset,1,1).
 6712%; End of file.
 6713%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 6714%; FILE: examples/Mueller2006/Chapter10/OneScreen.e
 6715%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 6716%;
 6717%; Copyright (c) 2005 IBM Corporation and others.
 6718%; All rights reserved. This program and the accompanying materials
 6719%; are made available under the terms of the Common Public License v1.0
 6720%; which accompanies this distribution, and is available at
 6721%; http://www.eclipse.org/legal/cpl-v10.html
 6722%;
 6723%; Contributors:
 6724%; IBM - Initial implementation
 6725%;
 6726%; @phdthesis{Cassimatis:2002,
 6727%;   author = "Nicholas L. Cassimatis",
 6728%;   year = "2002",
 6729%;   title = "Polyscheme: A Cognitive Architecture for Integrating Multiple Representation and Inference Schemes",
 6730%;   address = "Cambridge, MA",
 6731%;   school = "Program in Media Arts and Sciences, School of Architecture and Planning, Massachusetts Institute of Technology",
 6732%; }
 6733%;
 6734%; @book{Mueller:2006,
 6735%;   author = "Erik T. Mueller",
 6736%;   year = "2006",
 6737%;   title = "Commonsense Reasoning",
 6738%;   address = "San Francisco",
 6739%;   publisher = "Morgan Kaufmann/Elsevier",
 6740%; }
 6741%;
 6742
 6743% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2094
 6744% load foundations/Root.e
 6745
 6746% load foundations/EC.e
 6747
 6748% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2097
 6749% sort object
 6750% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2098
 6751==> sort(object).
 6752
 6753% sort location
 6754% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2099
 6755==> sort(location).
 6756
 6757% object O1, O2
 6758% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2101
 6759==> t(object,o1).
 6760==> t(object,o2).
 6761
 6762% location L1, L2, L3
 6763% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2102
 6764==> t(location,l1).
 6765==> t(location,l2).
 6766==> t(location,l3).
 6767
 6768% predicate Adjacent(location,location)
 6769 %  predicate(adjacent(location,location)).
 6770% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2104
 6771==> mpred_prop(adjacent(location,location),predicate).
 6772==> meta_argtypes(adjacent(location,location)).
 6773
 6774% predicate Equal(object,object)
 6775 %  predicate(equal(object,object)).
 6776% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2105
 6777==> mpred_prop(equal(object,object),predicate).
 6778==> meta_argtypes(equal(object,object)).
 6779
 6780% fluent At(object,location)
 6781 %  fluent(at(object,location)).
 6782% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2107
 6783==> mpred_prop(at(object,location),fluent).
 6784==> meta_argtypes(at(object,location)).
 6785
 6786% event Move(object,location,location)
 6787 %  event(move(object,location,location)).
 6788% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2108
 6789==> mpred_prop(move(object,location,location),event).
 6790==> meta_argtypes(move(object,location,location)).
 6791
 6792
 6793% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2109
 6794%; Sigma
 6795% [object,location1,location2,time]
 6796% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2112
 6797% HoldsAt(At(object,location1),time) &
 6798% Adjacent(location1,location2) ->
 6799% Initiates(Move(object,location1,location2),At(object,location2),time).
 6800% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2114
 6801axiom(initiates(move(Object, Location1, Location2), at(Object, Location2), Time),
 6802   
 6803    [ holds_at(at(Object, Location1), Time),
 6804      adjacent(Location1, Location2)
 6805    ]).
 6806
 6807
 6808% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2116
 6809% [object,location1,location2,time]
 6810% HoldsAt(At(object,location1),time) &
 6811% Adjacent(location1,location2) ->
 6812% Terminates(Move(object,location1,location2),At(object,location1),time).
 6813% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2119
 6814axiom(terminates(move(Object, Location1, Location2), at(Object, Location1), Time),
 6815   
 6816    [ holds_at(at(Object, Location1), Time),
 6817      adjacent(Location1, Location2)
 6818    ]).
 6819
 6820
 6821% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2121
 6822%; Psi
 6823% [object,location1,location2,time]
 6824% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2124
 6825% HoldsAt(At(object,location1),time) &
 6826% HoldsAt(At(object,location2),time) ->
 6827% location1=location2.
 6828% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2126
 6829axiom(Location1=Location2,
 6830   
 6831    [ holds_at(at(Object, Location1), Time),
 6832      holds_at(at(Object, Location2), Time)
 6833    ]).
 6834
 6835
 6836% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2128
 6837% [object,time]
 6838% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2129
 6839% {location} % HoldsAt(At(object,location),time).
 6840
 6841 /*  exists([Location],
 6842          holds_at(at(Object,Location),Time)).
 6843 */
 6844
 6845 /*  holds_at(at(At_Param, Location4), Time5) :-
 6846       some(Location4, '$kolem_Fn_352'(At_Param, Time5)).
 6847 */
 6848axiom(holds_at(at(At_Param, Location4), Time5),
 6849    [some(Location4, '$kolem_Fn_352'(At_Param, Time5))]).
 6850
 6851 /*  not(some(Location7, '$kolem_Fn_352'(Fn_352_Param, Time8))) :-
 6852       not(holds_at(at(Fn_352_Param, Location7), Time8)).
 6853 */
 6854axiom(not(some(Location7, '$kolem_Fn_352'(Fn_352_Param, Time8))),
 6855    [not(holds_at(at(Fn_352_Param, Location7), Time8))]).
 6856
 6857
 6858% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2131
 6859% [object1,object2,location,time]
 6860% HoldsAt(At(object1,location),time) &
 6861% HoldsAt(At(object2,location),time) ->
 6862% Equal(object1,object2).
 6863% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2134
 6864axiom(equal(Object1, Object2),
 6865   
 6866    [ holds_at(at(Object1, Location), Time),
 6867      holds_at(at(Object2, Location), Time)
 6868    ]).
 6869
 6870
 6871% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2136
 6872% [location1, location2]
 6873% Adjacent(location1,location2) <->
 6874% Adjacent(location2,location1).
 6875
 6876 /*  adjacent(Location1, Location2) <->
 6877       adjacent(Location2, Location1).
 6878 */
 6879% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2138
 6880axiom(adjacent(Location1, Location2),
 6881    [adjacent(Location2, Location1)]).
 6882axiom(adjacent(Location2, Location1),
 6883    [adjacent(Location1, Location2)]).
 6884
 6885
 6886% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2140
 6887% [object1,object2]
 6888% Equal(object1,object2) <->
 6889% Equal(object2,object1).
 6890
 6891 /*  equal(Object1, Object2) <->
 6892       equal(Object2, Object1).
 6893 */
 6894% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2142
 6895axiom(equal(Object1, Object2),
 6896    [equal(Object2, Object1)]).
 6897axiom(equal(Object2, Object1),
 6898    [equal(Object1, Object2)]).
 6899
 6900
 6901% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2144
 6902%; Gamma
 6903% [location1,location2]
 6904% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2147
 6905% Adjacent(location1,location2) <->
 6906% (location1=L1 & location2=L2) |
 6907% (location1=L2 & location2=L1) |
 6908% (location1=L2 & location2=L3) |
 6909% (location1=L3 & location2=L2).
 6910
 6911 /*  adjacent(Location1, Location2) <->
 6912       (   Location1=l1,
 6913           Location2=l2
 6914       ;   Location1=l2,
 6915           Location2=l1
 6916       ;   Location1=l2,
 6917           Location2=l3
 6918       ;   Location1=l3,
 6919           Location2=l2
 6920       ).
 6921 */
 6922% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2151
 6923axiom(adjacent(Location1, Location2),
 6924    [equals(Location1, l1), equals(Location2, l2)]).
 6925axiom(adjacent(Location1, Location2),
 6926    [equals(Location1, l2), equals(Location2, l1)]).
 6927axiom(adjacent(Location1, Location2),
 6928    [equals(Location1, l2), equals(Location2, l3)]).
 6929axiom(adjacent(Location1, Location2),
 6930    [equals(Location1, l3), equals(Location2, l2)]).
 6931
 6932 /*   if(adjacent(Location1, Location2),
 6933          (Location1=l1, Location2=l2;Location1=l2, Location2=l1;Location1=l2, Location2=l3;Location1=l3, Location2=l2)).
 6934 */
 6935
 6936 /*  not(adjacent(Adjacent_Param, Equals_Param)) :-
 6937       (   not(equals(Adjacent_Param, l1))
 6938       ;   not(equals(Equals_Param, l2))
 6939       ),
 6940       (   not(equals(Adjacent_Param, l2))
 6941       ;   not(equals(Equals_Param, l1))
 6942       ),
 6943       (   not(equals(Adjacent_Param, l2))
 6944       ;   not(equals(Equals_Param, l3))
 6945       ),
 6946       (   not(equals(Adjacent_Param, l3))
 6947       ;   not(equals(Equals_Param, l2))
 6948       ).
 6949 */
 6950axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 6951   
 6952    [ not(equals(Adjacent_Param, l3)),
 6953      not(equals(Adjacent_Param, l2)),
 6954      not(equals(Adjacent_Param, l2)),
 6955      not(equals(Adjacent_Param, l1))
 6956    ]).
 6957axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 6958   
 6959    [ not(equals(Equals_Param, l2)),
 6960      not(equals(Adjacent_Param, l2)),
 6961      not(equals(Adjacent_Param, l2)),
 6962      not(equals(Adjacent_Param, l1))
 6963    ]).
 6964axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 6965   
 6966    [ not(equals(Adjacent_Param, l3)),
 6967      not(equals(Equals_Param, l3)),
 6968      not(equals(Adjacent_Param, l2)),
 6969      not(equals(Adjacent_Param, l1))
 6970    ]).
 6971axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 6972   
 6973    [ not(equals(Equals_Param, l2)),
 6974      not(equals(Equals_Param, l3)),
 6975      not(equals(Adjacent_Param, l2)),
 6976      not(equals(Adjacent_Param, l1))
 6977    ]).
 6978axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 6979   
 6980    [ not(equals(Adjacent_Param, l3)),
 6981      not(equals(Adjacent_Param, l2)),
 6982      not(equals(Equals_Param, l1)),
 6983      not(equals(Adjacent_Param, l1))
 6984    ]).
 6985axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 6986   
 6987    [ not(equals(Equals_Param, l2)),
 6988      not(equals(Adjacent_Param, l2)),
 6989      not(equals(Equals_Param, l1)),
 6990      not(equals(Adjacent_Param, l1))
 6991    ]).
 6992axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 6993   
 6994    [ not(equals(Adjacent_Param, l3)),
 6995      not(equals(Equals_Param, l3)),
 6996      not(equals(Equals_Param, l1)),
 6997      not(equals(Adjacent_Param, l1))
 6998    ]).
 6999axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7000   
 7001    [ not(equals(Equals_Param, l2)),
 7002      not(equals(Equals_Param, l3)),
 7003      not(equals(Equals_Param, l1)),
 7004      not(equals(Adjacent_Param, l1))
 7005    ]).
 7006axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7007   
 7008    [ not(equals(Adjacent_Param, l3)),
 7009      not(equals(Adjacent_Param, l2)),
 7010      not(equals(Adjacent_Param, l2)),
 7011      not(equals(Equals_Param, l2))
 7012    ]).
 7013axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7014   
 7015    [ not(equals(Equals_Param, l2)),
 7016      not(equals(Adjacent_Param, l2)),
 7017      not(equals(Adjacent_Param, l2)),
 7018      not(equals(Equals_Param, l2))
 7019    ]).
 7020axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7021   
 7022    [ not(equals(Adjacent_Param, l3)),
 7023      not(equals(Equals_Param, l3)),
 7024      not(equals(Adjacent_Param, l2)),
 7025      not(equals(Equals_Param, l2))
 7026    ]).
 7027axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7028   
 7029    [ not(equals(Equals_Param, l2)),
 7030      not(equals(Equals_Param, l3)),
 7031      not(equals(Adjacent_Param, l2)),
 7032      not(equals(Equals_Param, l2))
 7033    ]).
 7034axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7035   
 7036    [ not(equals(Adjacent_Param, l3)),
 7037      not(equals(Adjacent_Param, l2)),
 7038      not(equals(Equals_Param, l1)),
 7039      not(equals(Equals_Param, l2))
 7040    ]).
 7041axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7042   
 7043    [ not(equals(Equals_Param, l2)),
 7044      not(equals(Adjacent_Param, l2)),
 7045      not(equals(Equals_Param, l1)),
 7046      not(equals(Equals_Param, l2))
 7047    ]).
 7048axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7049   
 7050    [ not(equals(Adjacent_Param, l3)),
 7051      not(equals(Equals_Param, l3)),
 7052      not(equals(Equals_Param, l1)),
 7053      not(equals(Equals_Param, l2))
 7054    ]).
 7055axiom(not(adjacent(Adjacent_Param, Equals_Param)),
 7056   
 7057    [ not(equals(Equals_Param, l2)),
 7058      not(equals(Equals_Param, l3)),
 7059      not(equals(Equals_Param, l1)),
 7060      not(equals(Equals_Param, l2))
 7061    ]).
 7062
 7063 /*  equals(Equals_Param4, l1) :-
 7064       ( (   not(equals(Equals_Param4, l2))
 7065         ;   not(equals(Equals_Param5, l1))
 7066         ),
 7067         (   not(equals(Equals_Param4, l2))
 7068         ;   not(equals(Equals_Param5, l3))
 7069         ),
 7070         (   not(equals(Equals_Param4, l3))
 7071         ;   not(equals(Equals_Param5, l2))
 7072         )
 7073       ),
 7074       adjacent(Equals_Param4, Equals_Param5).
 7075 */
 7076axiom(equals(Equals_Param4, l1),
 7077   
 7078    [ not(equals(Equals_Param4, l3)),
 7079      not(equals(Equals_Param4, l2)),
 7080      not(equals(Equals_Param4, l2)),
 7081      adjacent(Equals_Param4, Equals_Param5)
 7082    ]).
 7083axiom(equals(Equals_Param4, l1),
 7084   
 7085    [ not(equals(Equals_Param5, l2)),
 7086      not(equals(Equals_Param4, l2)),
 7087      not(equals(Equals_Param4, l2)),
 7088      adjacent(Equals_Param4, Equals_Param5)
 7089    ]).
 7090axiom(equals(Equals_Param4, l1),
 7091   
 7092    [ not(equals(Equals_Param4, l3)),
 7093      not(equals(Equals_Param5, l3)),
 7094      not(equals(Equals_Param4, l2)),
 7095      adjacent(Equals_Param4, Equals_Param5)
 7096    ]).
 7097axiom(equals(Equals_Param4, l1),
 7098   
 7099    [ not(equals(Equals_Param5, l2)),
 7100      not(equals(Equals_Param5, l3)),
 7101      not(equals(Equals_Param4, l2)),
 7102      adjacent(Equals_Param4, Equals_Param5)
 7103    ]).
 7104axiom(equals(Equals_Param4, l1),
 7105   
 7106    [ not(equals(Equals_Param4, l3)),
 7107      not(equals(Equals_Param4, l2)),
 7108      not(equals(Equals_Param5, l1)),
 7109      adjacent(Equals_Param4, Equals_Param5)
 7110    ]).
 7111axiom(equals(Equals_Param4, l1),
 7112   
 7113    [ not(equals(Equals_Param5, l2)),
 7114      not(equals(Equals_Param4, l2)),
 7115      not(equals(Equals_Param5, l1)),
 7116      adjacent(Equals_Param4, Equals_Param5)
 7117    ]).
 7118axiom(equals(Equals_Param4, l1),
 7119   
 7120    [ not(equals(Equals_Param4, l3)),
 7121      not(equals(Equals_Param5, l3)),
 7122      not(equals(Equals_Param5, l1)),
 7123      adjacent(Equals_Param4, Equals_Param5)
 7124    ]).
 7125axiom(equals(Equals_Param4, l1),
 7126   
 7127    [ not(equals(Equals_Param5, l2)),
 7128      not(equals(Equals_Param5, l3)),
 7129      not(equals(Equals_Param5, l1)),
 7130      adjacent(Equals_Param4, Equals_Param5)
 7131    ]).
 7132
 7133 /*  equals(Equals_Param6, l2) :-
 7134       ( (   not(equals(Equals_Param7, l2))
 7135         ;   not(equals(Equals_Param6, l1))
 7136         ),
 7137         (   not(equals(Equals_Param7, l2))
 7138         ;   not(equals(Equals_Param6, l3))
 7139         ),
 7140         (   not(equals(Equals_Param7, l3))
 7141         ;   not(equals(Equals_Param6, l2))
 7142         )
 7143       ),
 7144       adjacent(Equals_Param7, Equals_Param6).
 7145 */
 7146axiom(equals(Equals_Param6, l2),
 7147   
 7148    [ not(equals(Equals_Param7, l3)),
 7149      not(equals(Equals_Param7, l2)),
 7150      not(equals(Equals_Param7, l2)),
 7151      adjacent(Equals_Param7, Equals_Param6)
 7152    ]).
 7153axiom(equals(Equals_Param6, l2),
 7154   
 7155    [ not(equals(Equals_Param6, l2)),
 7156      not(equals(Equals_Param7, l2)),
 7157      not(equals(Equals_Param7, l2)),
 7158      adjacent(Equals_Param7, Equals_Param6)
 7159    ]).
 7160axiom(equals(Equals_Param6, l2),
 7161   
 7162    [ not(equals(Equals_Param7, l3)),
 7163      not(equals(Equals_Param6, l3)),
 7164      not(equals(Equals_Param7, l2)),
 7165      adjacent(Equals_Param7, Equals_Param6)
 7166    ]).
 7167axiom(equals(Equals_Param6, l2),
 7168   
 7169    [ not(equals(Equals_Param6, l2)),
 7170      not(equals(Equals_Param6, l3)),
 7171      not(equals(Equals_Param7, l2)),
 7172      adjacent(Equals_Param7, Equals_Param6)
 7173    ]).
 7174axiom(equals(Equals_Param6, l2),
 7175   
 7176    [ not(equals(Equals_Param7, l3)),
 7177      not(equals(Equals_Param7, l2)),
 7178      not(equals(Equals_Param6, l1)),
 7179      adjacent(Equals_Param7, Equals_Param6)
 7180    ]).
 7181axiom(equals(Equals_Param6, l2),
 7182   
 7183    [ not(equals(Equals_Param6, l2)),
 7184      not(equals(Equals_Param7, l2)),
 7185      not(equals(Equals_Param6, l1)),
 7186      adjacent(Equals_Param7, Equals_Param6)
 7187    ]).
 7188axiom(equals(Equals_Param6, l2),
 7189   
 7190    [ not(equals(Equals_Param7, l3)),
 7191      not(equals(Equals_Param6, l3)),
 7192      not(equals(Equals_Param6, l1)),
 7193      adjacent(Equals_Param7, Equals_Param6)
 7194    ]).
 7195axiom(equals(Equals_Param6, l2),
 7196   
 7197    [ not(equals(Equals_Param6, l2)),
 7198      not(equals(Equals_Param6, l3)),
 7199      not(equals(Equals_Param6, l1)),
 7200      adjacent(Equals_Param7, Equals_Param6)
 7201    ]).
 7202
 7203 /*  equals(Equals_Param8, l2) :-
 7204       ( (   not(equals(Equals_Param8, l2))
 7205         ;   not(equals(Equals_Param9, l3))
 7206         ),
 7207         (   not(equals(Equals_Param8, l3))
 7208         ;   not(equals(Equals_Param9, l2))
 7209         )
 7210       ),
 7211       (   not(equals(Equals_Param8, l1))
 7212       ;   not(equals(Equals_Param9, l2))
 7213       ),
 7214       adjacent(Equals_Param8, Equals_Param9).
 7215 */
 7216axiom(equals(Equals_Param8, l2),
 7217   
 7218    [ not(equals(Equals_Param8, l1)),
 7219      not(equals(Equals_Param8, l3)),
 7220      not(equals(Equals_Param8, l2)),
 7221      adjacent(Equals_Param8, Equals_Param9)
 7222    ]).
 7223axiom(equals(Equals_Param8, l2),
 7224   
 7225    [ not(equals(Equals_Param9, l2)),
 7226      not(equals(Equals_Param8, l3)),
 7227      not(equals(Equals_Param8, l2)),
 7228      adjacent(Equals_Param8, Equals_Param9)
 7229    ]).
 7230axiom(equals(Equals_Param8, l2),
 7231   
 7232    [ not(equals(Equals_Param8, l1)),
 7233      not(equals(Equals_Param9, l2)),
 7234      not(equals(Equals_Param8, l2)),
 7235      adjacent(Equals_Param8, Equals_Param9)
 7236    ]).
 7237axiom(equals(Equals_Param8, l2),
 7238   
 7239    [ not(equals(Equals_Param9, l2)),
 7240      not(equals(Equals_Param9, l2)),
 7241      not(equals(Equals_Param8, l2)),
 7242      adjacent(Equals_Param8, Equals_Param9)
 7243    ]).
 7244axiom(equals(Equals_Param8, l2),
 7245   
 7246    [ not(equals(Equals_Param8, l1)),
 7247      not(equals(Equals_Param8, l3)),
 7248      not(equals(Equals_Param9, l3)),
 7249      adjacent(Equals_Param8, Equals_Param9)
 7250    ]).
 7251axiom(equals(Equals_Param8, l2),
 7252   
 7253    [ not(equals(Equals_Param9, l2)),
 7254      not(equals(Equals_Param8, l3)),
 7255      not(equals(Equals_Param9, l3)),
 7256      adjacent(Equals_Param8, Equals_Param9)
 7257    ]).
 7258axiom(equals(Equals_Param8, l2),
 7259   
 7260    [ not(equals(Equals_Param8, l1)),
 7261      not(equals(Equals_Param9, l2)),
 7262      not(equals(Equals_Param9, l3)),
 7263      adjacent(Equals_Param8, Equals_Param9)
 7264    ]).
 7265axiom(equals(Equals_Param8, l2),
 7266   
 7267    [ not(equals(Equals_Param9, l2)),
 7268      not(equals(Equals_Param9, l2)),
 7269      not(equals(Equals_Param9, l3)),
 7270      adjacent(Equals_Param8, Equals_Param9)
 7271    ]).
 7272
 7273 /*  equals(Equals_Param10, l1) :-
 7274       ( (   not(equals(Equals_Param11, l2))
 7275         ;   not(equals(Equals_Param10, l3))
 7276         ),
 7277         (   not(equals(Equals_Param11, l3))
 7278         ;   not(equals(Equals_Param10, l2))
 7279         )
 7280       ),
 7281       (   not(equals(Equals_Param11, l1))
 7282       ;   not(equals(Equals_Param10, l2))
 7283       ),
 7284       adjacent(Equals_Param11, Equals_Param10).
 7285 */
 7286axiom(equals(Equals_Param10, l1),
 7287   
 7288    [ not(equals(Equals_Param11, l1)),
 7289      not(equals(Equals_Param11, l3)),
 7290      not(equals(Equals_Param11, l2)),
 7291      adjacent(Equals_Param11, Equals_Param10)
 7292    ]).
 7293axiom(equals(Equals_Param10, l1),
 7294   
 7295    [ not(equals(Equals_Param10, l2)),
 7296      not(equals(Equals_Param11, l3)),
 7297      not(equals(Equals_Param11, l2)),
 7298      adjacent(Equals_Param11, Equals_Param10)
 7299    ]).
 7300axiom(equals(Equals_Param10, l1),
 7301   
 7302    [ not(equals(Equals_Param11, l1)),
 7303      not(equals(Equals_Param10, l2)),
 7304      not(equals(Equals_Param11, l2)),
 7305      adjacent(Equals_Param11, Equals_Param10)
 7306    ]).
 7307axiom(equals(Equals_Param10, l1),
 7308   
 7309    [ not(equals(Equals_Param10, l2)),
 7310      not(equals(Equals_Param10, l2)),
 7311      not(equals(Equals_Param11, l2)),
 7312      adjacent(Equals_Param11, Equals_Param10)
 7313    ]).
 7314axiom(equals(Equals_Param10, l1),
 7315   
 7316    [ not(equals(Equals_Param11, l1)),
 7317      not(equals(Equals_Param11, l3)),
 7318      not(equals(Equals_Param10, l3)),
 7319      adjacent(Equals_Param11, Equals_Param10)
 7320    ]).
 7321axiom(equals(Equals_Param10, l1),
 7322   
 7323    [ not(equals(Equals_Param10, l2)),
 7324      not(equals(Equals_Param11, l3)),
 7325      not(equals(Equals_Param10, l3)),
 7326      adjacent(Equals_Param11, Equals_Param10)
 7327    ]).
 7328axiom(equals(Equals_Param10, l1),
 7329   
 7330    [ not(equals(Equals_Param11, l1)),
 7331      not(equals(Equals_Param10, l2)),
 7332      not(equals(Equals_Param10, l3)),
 7333      adjacent(Equals_Param11, Equals_Param10)
 7334    ]).
 7335axiom(equals(Equals_Param10, l1),
 7336   
 7337    [ not(equals(Equals_Param10, l2)),
 7338      not(equals(Equals_Param10, l2)),
 7339      not(equals(Equals_Param10, l3)),
 7340      adjacent(Equals_Param11, Equals_Param10)
 7341    ]).
 7342
 7343 /*  equals(Equals_Param12, l2) :-
 7344       (   not(equals(Equals_Param12, l3))
 7345       ;   not(equals(Equals_Param13, l2))
 7346       ),
 7347       (   not(equals(Equals_Param12, l2))
 7348       ;   not(equals(Equals_Param13, l1))
 7349       ),
 7350       (   not(equals(Equals_Param12, l1))
 7351       ;   not(equals(Equals_Param13, l2))
 7352       ),
 7353       adjacent(Equals_Param12, Equals_Param13).
 7354 */
 7355axiom(equals(Equals_Param12, l2),
 7356   
 7357    [ not(equals(Equals_Param12, l1)),
 7358      not(equals(Equals_Param12, l2)),
 7359      not(equals(Equals_Param12, l3)),
 7360      adjacent(Equals_Param12, Equals_Param13)
 7361    ]).
 7362axiom(equals(Equals_Param12, l2),
 7363   
 7364    [ not(equals(Equals_Param13, l2)),
 7365      not(equals(Equals_Param12, l2)),
 7366      not(equals(Equals_Param12, l3)),
 7367      adjacent(Equals_Param12, Equals_Param13)
 7368    ]).
 7369axiom(equals(Equals_Param12, l2),
 7370   
 7371    [ not(equals(Equals_Param12, l1)),
 7372      not(equals(Equals_Param13, l1)),
 7373      not(equals(Equals_Param12, l3)),
 7374      adjacent(Equals_Param12, Equals_Param13)
 7375    ]).
 7376axiom(equals(Equals_Param12, l2),
 7377   
 7378    [ not(equals(Equals_Param13, l2)),
 7379      not(equals(Equals_Param13, l1)),
 7380      not(equals(Equals_Param12, l3)),
 7381      adjacent(Equals_Param12, Equals_Param13)
 7382    ]).
 7383axiom(equals(Equals_Param12, l2),
 7384   
 7385    [ not(equals(Equals_Param12, l1)),
 7386      not(equals(Equals_Param12, l2)),
 7387      not(equals(Equals_Param13, l2)),
 7388      adjacent(Equals_Param12, Equals_Param13)
 7389    ]).
 7390axiom(equals(Equals_Param12, l2),
 7391   
 7392    [ not(equals(Equals_Param13, l2)),
 7393      not(equals(Equals_Param12, l2)),
 7394      not(equals(Equals_Param13, l2)),
 7395      adjacent(Equals_Param12, Equals_Param13)
 7396    ]).
 7397axiom(equals(Equals_Param12, l2),
 7398   
 7399    [ not(equals(Equals_Param12, l1)),
 7400      not(equals(Equals_Param13, l1)),
 7401      not(equals(Equals_Param13, l2)),
 7402      adjacent(Equals_Param12, Equals_Param13)
 7403    ]).
 7404axiom(equals(Equals_Param12, l2),
 7405   
 7406    [ not(equals(Equals_Param13, l2)),
 7407      not(equals(Equals_Param13, l1)),
 7408      not(equals(Equals_Param13, l2)),
 7409      adjacent(Equals_Param12, Equals_Param13)
 7410    ]).
 7411
 7412 /*  equals(Equals_Param14, l3) :-
 7413       (   not(equals(Equals_Param15, l3))
 7414       ;   not(equals(Equals_Param14, l2))
 7415       ),
 7416       (   not(equals(Equals_Param15, l2))
 7417       ;   not(equals(Equals_Param14, l1))
 7418       ),
 7419       (   not(equals(Equals_Param15, l1))
 7420       ;   not(equals(Equals_Param14, l2))
 7421       ),
 7422       adjacent(Equals_Param15, Equals_Param14).
 7423 */
 7424axiom(equals(Equals_Param14, l3),
 7425   
 7426    [ not(equals(Equals_Param15, l1)),
 7427      not(equals(Equals_Param15, l2)),
 7428      not(equals(Equals_Param15, l3)),
 7429      adjacent(Equals_Param15, Equals_Param14)
 7430    ]).
 7431axiom(equals(Equals_Param14, l3),
 7432   
 7433    [ not(equals(Equals_Param14, l2)),
 7434      not(equals(Equals_Param15, l2)),
 7435      not(equals(Equals_Param15, l3)),
 7436      adjacent(Equals_Param15, Equals_Param14)
 7437    ]).
 7438axiom(equals(Equals_Param14, l3),
 7439   
 7440    [ not(equals(Equals_Param15, l1)),
 7441      not(equals(Equals_Param14, l1)),
 7442      not(equals(Equals_Param15, l3)),
 7443      adjacent(Equals_Param15, Equals_Param14)
 7444    ]).
 7445axiom(equals(Equals_Param14, l3),
 7446   
 7447    [ not(equals(Equals_Param14, l2)),
 7448      not(equals(Equals_Param14, l1)),
 7449      not(equals(Equals_Param15, l3)),
 7450      adjacent(Equals_Param15, Equals_Param14)
 7451    ]).
 7452axiom(equals(Equals_Param14, l3),
 7453   
 7454    [ not(equals(Equals_Param15, l1)),
 7455      not(equals(Equals_Param15, l2)),
 7456      not(equals(Equals_Param14, l2)),
 7457      adjacent(Equals_Param15, Equals_Param14)
 7458    ]).
 7459axiom(equals(Equals_Param14, l3),
 7460   
 7461    [ not(equals(Equals_Param14, l2)),
 7462      not(equals(Equals_Param15, l2)),
 7463      not(equals(Equals_Param14, l2)),
 7464      adjacent(Equals_Param15, Equals_Param14)
 7465    ]).
 7466axiom(equals(Equals_Param14, l3),
 7467   
 7468    [ not(equals(Equals_Param15, l1)),
 7469      not(equals(Equals_Param14, l1)),
 7470      not(equals(Equals_Param14, l2)),
 7471      adjacent(Equals_Param15, Equals_Param14)
 7472    ]).
 7473axiom(equals(Equals_Param14, l3),
 7474   
 7475    [ not(equals(Equals_Param14, l2)),
 7476      not(equals(Equals_Param14, l1)),
 7477      not(equals(Equals_Param14, l2)),
 7478      adjacent(Equals_Param15, Equals_Param14)
 7479    ]).
 7480
 7481 /*  equals(Equals_Param16, l3) :-
 7482       (   not(equals(Equals_Param16, l2))
 7483       ;   not(equals(Equals_Param17, l3))
 7484       ),
 7485       (   not(equals(Equals_Param16, l2))
 7486       ;   not(equals(Equals_Param17, l1))
 7487       ),
 7488       (   not(equals(Equals_Param16, l1))
 7489       ;   not(equals(Equals_Param17, l2))
 7490       ),
 7491       adjacent(Equals_Param16, Equals_Param17).
 7492 */
 7493axiom(equals(Equals_Param16, l3),
 7494   
 7495    [ not(equals(Equals_Param16, l1)),
 7496      not(equals(Equals_Param16, l2)),
 7497      not(equals(Equals_Param16, l2)),
 7498      adjacent(Equals_Param16, Equals_Param17)
 7499    ]).
 7500axiom(equals(Equals_Param16, l3),
 7501   
 7502    [ not(equals(Equals_Param17, l2)),
 7503      not(equals(Equals_Param16, l2)),
 7504      not(equals(Equals_Param16, l2)),
 7505      adjacent(Equals_Param16, Equals_Param17)
 7506    ]).
 7507axiom(equals(Equals_Param16, l3),
 7508   
 7509    [ not(equals(Equals_Param16, l1)),
 7510      not(equals(Equals_Param17, l1)),
 7511      not(equals(Equals_Param16, l2)),
 7512      adjacent(Equals_Param16, Equals_Param17)
 7513    ]).
 7514axiom(equals(Equals_Param16, l3),
 7515   
 7516    [ not(equals(Equals_Param17, l2)),
 7517      not(equals(Equals_Param17, l1)),
 7518      not(equals(Equals_Param16, l2)),
 7519      adjacent(Equals_Param16, Equals_Param17)
 7520    ]).
 7521axiom(equals(Equals_Param16, l3),
 7522   
 7523    [ not(equals(Equals_Param16, l1)),
 7524      not(equals(Equals_Param16, l2)),
 7525      not(equals(Equals_Param17, l3)),
 7526      adjacent(Equals_Param16, Equals_Param17)
 7527    ]).
 7528axiom(equals(Equals_Param16, l3),
 7529   
 7530    [ not(equals(Equals_Param17, l2)),
 7531      not(equals(Equals_Param16, l2)),
 7532      not(equals(Equals_Param17, l3)),
 7533      adjacent(Equals_Param16, Equals_Param17)
 7534    ]).
 7535axiom(equals(Equals_Param16, l3),
 7536   
 7537    [ not(equals(Equals_Param16, l1)),
 7538      not(equals(Equals_Param17, l1)),
 7539      not(equals(Equals_Param17, l3)),
 7540      adjacent(Equals_Param16, Equals_Param17)
 7541    ]).
 7542axiom(equals(Equals_Param16, l3),
 7543   
 7544    [ not(equals(Equals_Param17, l2)),
 7545      not(equals(Equals_Param17, l1)),
 7546      not(equals(Equals_Param17, l3)),
 7547      adjacent(Equals_Param16, Equals_Param17)
 7548    ]).
 7549
 7550 /*  equals(Equals_Param18, l2) :-
 7551       (   not(equals(Equals_Param19, l2))
 7552       ;   not(equals(Equals_Param18, l3))
 7553       ),
 7554       (   not(equals(Equals_Param19, l2))
 7555       ;   not(equals(Equals_Param18, l1))
 7556       ),
 7557       (   not(equals(Equals_Param19, l1))
 7558       ;   not(equals(Equals_Param18, l2))
 7559       ),
 7560       adjacent(Equals_Param19, Equals_Param18).
 7561 */
 7562axiom(equals(Equals_Param18, l2),
 7563   
 7564    [ not(equals(Equals_Param19, l1)),
 7565      not(equals(Equals_Param19, l2)),
 7566      not(equals(Equals_Param19, l2)),
 7567      adjacent(Equals_Param19, Equals_Param18)
 7568    ]).
 7569axiom(equals(Equals_Param18, l2),
 7570   
 7571    [ not(equals(Equals_Param18, l2)),
 7572      not(equals(Equals_Param19, l2)),
 7573      not(equals(Equals_Param19, l2)),
 7574      adjacent(Equals_Param19, Equals_Param18)
 7575    ]).
 7576axiom(equals(Equals_Param18, l2),
 7577   
 7578    [ not(equals(Equals_Param19, l1)),
 7579      not(equals(Equals_Param18, l1)),
 7580      not(equals(Equals_Param19, l2)),
 7581      adjacent(Equals_Param19, Equals_Param18)
 7582    ]).
 7583axiom(equals(Equals_Param18, l2),
 7584   
 7585    [ not(equals(Equals_Param18, l2)),
 7586      not(equals(Equals_Param18, l1)),
 7587      not(equals(Equals_Param19, l2)),
 7588      adjacent(Equals_Param19, Equals_Param18)
 7589    ]).
 7590axiom(equals(Equals_Param18, l2),
 7591   
 7592    [ not(equals(Equals_Param19, l1)),
 7593      not(equals(Equals_Param19, l2)),
 7594      not(equals(Equals_Param18, l3)),
 7595      adjacent(Equals_Param19, Equals_Param18)
 7596    ]).
 7597axiom(equals(Equals_Param18, l2),
 7598   
 7599    [ not(equals(Equals_Param18, l2)),
 7600      not(equals(Equals_Param19, l2)),
 7601      not(equals(Equals_Param18, l3)),
 7602      adjacent(Equals_Param19, Equals_Param18)
 7603    ]).
 7604axiom(equals(Equals_Param18, l2),
 7605   
 7606    [ not(equals(Equals_Param19, l1)),
 7607      not(equals(Equals_Param18, l1)),
 7608      not(equals(Equals_Param18, l3)),
 7609      adjacent(Equals_Param19, Equals_Param18)
 7610    ]).
 7611axiom(equals(Equals_Param18, l2),
 7612   
 7613    [ not(equals(Equals_Param18, l2)),
 7614      not(equals(Equals_Param18, l1)),
 7615      not(equals(Equals_Param18, l3)),
 7616      adjacent(Equals_Param19, Equals_Param18)
 7617    ]).
 7618
 7619
 7620% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2153
 7621% HoldsAt(At(O1,L1),0).
 7622axiom(initially(at(o1, l1)),
 7623    []).
 7624
 7625
 7626% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2154
 7627% [object]
 7628 % !HoldsAt(At(object,L3),0).
 7629 %  not(initially(at(Object,l3))).
 7630axiom(not(initially(at(At_Param, l3))),
 7631    []).
 7632
 7633
 7634% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2156
 7635% [object]
 7636 % !HoldsAt(At(object,L1),1).
 7637 %  not(holds_at(at(Object,l1),1)).
 7638axiom(not(holds_at(at(At_Param, l1), start)),
 7639    [b(t, start), ignore(t+1=start)]).
 7640
 7641
 7642% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2157
 7643% [object]
 7644 % !HoldsAt(At(object,L3),1).
 7645 %  not(holds_at(at(Object,l3),1)).
 7646axiom(not(holds_at(at(At_Param, l3), start)),
 7647    [b(t, start), ignore(t+1=start)]).
 7648
 7649
 7650% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2159
 7651% HoldsAt(At(O2,L3),2).
 7652holds_at(at(o2,l3),2).
 7653
 7654
 7655% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2160
 7656% [object]
 7657 % !HoldsAt(At(object,L1),2).
 7658 %  not(holds_at(at(Object,l1),2)).
 7659axiom(not(holds_at(at(At_Param, l1), t2)),
 7660    [b(t, t2), ignore(t+2=t2)]).
 7661
 7662
 7663% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2162
 7664%; ADDED:
 7665% [object,location1,location2,time]
 7666% Happens(Move(object,location1,location2),time) ->
 7667% HoldsAt(At(object,location1),time) &
 7668% Adjacent(location1,location2).
 7669% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2166
 7670axiom(requires(move(Object, Location1, Location2), Time),
 7671   
 7672    [ holds_at(at(Object, Location1), Time),
 7673      adjacent(Location1, Location2)
 7674    ]).
 7675
 7676
 7677% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2168
 7678% [object1,object2,location1,location2,time]
 7679% Equal(object1,object2) &
 7680% Happens(Move(object1,location1,location2),time) ->
 7681% Happens(Move(object2,location1,location2),time).
 7682% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2171
 7683axiom(happens(move(Object2, Location1, Location2), Time),
 7684   
 7685    [ equal(Object1, Object2),
 7686      happens(move(Object1, Location1, Location2), Time)
 7687    ]).
 7688
 7689% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2173
 7690% range time 0 2
 7691% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2174
 7692==> range(time,0,2).
 7693
 7694% range offset 1 1
 7695% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2175
 7696==> range(offset,1,1).
 7697%; End of file.
 7698%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 7699%; FILE: examples/Mueller2006/Chapter9/RunningAndDriving.e
 7700%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 7701%;
 7702%; Copyright (c) 2005 IBM Corporation and others.
 7703%; All rights reserved. This program and the accompanying materials
 7704%; are made available under the terms of the Common Public License v1.0
 7705%; which accompanies this distribution, and is available at
 7706%; http://www.eclipse.org/legal/cpl-v10.html
 7707%;
 7708%; Contributors:
 7709%; IBM - Initial implementation
 7710%;
 7711%; @book{Mueller:2006,
 7712%;   author = "Erik T. Mueller",
 7713%;   year = "2006",
 7714%;   title = "Commonsense Reasoning",
 7715%;   address = "San Francisco",
 7716%;   publisher = "Morgan Kaufmann/Elsevier",
 7717%; }
 7718%;
 7719
 7720% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2202
 7721% load foundations/Root.e
 7722
 7723% load foundations/EC.e
 7724
 7725% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2205
 7726% sort agent
 7727% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2206
 7728==> sort(agent).
 7729
 7730% sort location
 7731% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2207
 7732==> sort(location).
 7733
 7734% agent James
 7735% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2209
 7736==> t(agent,james).
 7737
 7738% location Bookstore
 7739% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2210
 7740==> t(location,bookstore).
 7741
 7742% fluent Tired(agent)
 7743 %  fluent(tired(agent)).
 7744% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2212
 7745==> mpred_prop(tired(agent),fluent).
 7746==> meta_argtypes(tired(agent)).
 7747
 7748% event Go(agent,location)
 7749 %  event(go(agent,location)).
 7750% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2214
 7751==> mpred_prop(go(agent,location),event).
 7752==> meta_argtypes(go(agent,location)).
 7753
 7754% event Run(agent,location)
 7755 %  event(run(agent,location)).
 7756% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2215
 7757==> mpred_prop(run(agent,location),event).
 7758==> meta_argtypes(run(agent,location)).
 7759
 7760% event Drive(agent,location)
 7761 %  event(drive(agent,location)).
 7762% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2216
 7763==> mpred_prop(drive(agent,location),event).
 7764==> meta_argtypes(drive(agent,location)).
 7765
 7766
 7767% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2217
 7768% [agent,location,time]
 7769% Happens(Go(agent,location),time) ->
 7770% Happens(Run(agent,location),time) | Happens(Drive(agent,location),time).
 7771
 7772 /*   if(happens(go(Agent, Location), Time),
 7773          (happens(run(Agent, Location), Time);happens(drive(Agent, Location), Time))).
 7774 */
 7775
 7776 /*  happens(run(Run_Param, Run_Ret), Maptime) :-
 7777       not(happens(drive(Run_Param, Run_Ret), Maptime)),
 7778       happens(go(Run_Param, Run_Ret), Maptime).
 7779 */
 7780% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2219
 7781axiom(happens(run(Run_Param, Run_Ret), Maptime),
 7782   
 7783    [ not(happens(drive(Run_Param, Run_Ret), Maptime)),
 7784      happens(go(Run_Param, Run_Ret), Maptime)
 7785    ]).
 7786
 7787 /*  happens(drive(Drive_Param, Drive_Ret), Maptime6) :-
 7788       not(happens(run(Drive_Param, Drive_Ret), Maptime6)),
 7789       happens(go(Drive_Param, Drive_Ret), Maptime6).
 7790 */
 7791axiom(happens(drive(Drive_Param, Drive_Ret), Maptime6),
 7792   
 7793    [ not(happens(run(Drive_Param, Drive_Ret), Maptime6)),
 7794      happens(go(Drive_Param, Drive_Ret), Maptime6)
 7795    ]).
 7796
 7797 /*  not(happens(go(Go_Param, Go_Ret), Maptime9)) :-
 7798       not(happens(run(Go_Param, Go_Ret), Maptime9)),
 7799       not(happens(drive(Go_Param, Go_Ret), Maptime9)).
 7800 */
 7801axiom(not(happens(go(Go_Param, Go_Ret), Maptime9)),
 7802   
 7803    [ not(happens(run(Go_Param, Go_Ret), Maptime9)),
 7804      not(happens(drive(Go_Param, Go_Ret), Maptime9))
 7805    ]).
 7806
 7807% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2221
 7808% xor Run, Drive
 7809% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2222
 7810xor([run,drive]).
 7811
 7812
 7813% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2223
 7814% [agent,location,time]
 7815 % Initiates(Run(agent,location),Tired(agent),time).
 7816axiom(initiates(run(Agent, Location), tired(Agent), Time),
 7817    []).
 7818
 7819
 7820% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2225
 7821% !HoldsAt(Tired(James),0).
 7822 %  not(initially(tired(james))).
 7823axiom(not(initially(tired(james))),
 7824    []).
 7825
 7826
 7827% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2226
 7828% Happens(Go(James,Bookstore),0).
 7829axiom(happens(go(james, bookstore), t),
 7830    [is_time(0)]).
 7831
 7832
 7833% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2227
 7834% HoldsAt(Tired(James),1).
 7835holds_at(tired(james),1).
 7836
 7837% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2229
 7838% range time 0 1
 7839% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2230
 7840==> range(time,0,1).
 7841
 7842% range offset 1 1
 7843% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2231
 7844==> range(offset,1,1).
 7845%; End of file.
 7846%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 7847%; FILE: examples/Mueller2006/Chapter9/RouletteWheel.e
 7848%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 7849%;
 7850%; Copyright (c) 2005 IBM Corporation and others.
 7851%; All rights reserved. This program and the accompanying materials
 7852%; are made available under the terms of the Common Public License v1.0
 7853%; which accompanies this distribution, and is available at
 7854%; http://www.eclipse.org/legal/cpl-v10.html
 7855%;
 7856%; Contributors:
 7857%; IBM - Initial implementation
 7858%;
 7859%; @book{Mueller:2006,
 7860%;   author = "Erik T. Mueller",
 7861%;   year = "2006",
 7862%;   title = "Commonsense Reasoning",
 7863%;   address = "San Francisco",
 7864%;   publisher = "Morgan Kaufmann/Elsevier",
 7865%; }
 7866%;
 7867
 7868% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2258
 7869% option modeldiff on
 7870% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2259
 7871:- set_ec_option(modeldiff, on). 7872
 7873% load foundations/Root.e
 7874
 7875% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2261
 7876% load foundations/EC.e
 7877
 7878% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2263
 7879% sort dealer
 7880% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2264
 7881==> sort(dealer).
 7882
 7883% sort wheel
 7884% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2265
 7885==> sort(wheel).
 7886
 7887% sort value: integer
 7888% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2266
 7889==> subsort(value,integer).
 7890
 7891% wheel Wheel1
 7892% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2268
 7893==> t(wheel,wheel1).
 7894
 7895% dealer Dealer1
 7896% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2269
 7897==> t(dealer,dealer1).
 7898
 7899% fluent WheelNumberDeterminer(wheel,value)
 7900 %  fluent(wheelNumberDeterminer(wheel,value)).
 7901% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2271
 7902==> mpred_prop(wheelNumberDeterminer(wheel,value),fluent).
 7903==> meta_argtypes(wheelNumberDeterminer(wheel,value)).
 7904
 7905% fluent WheelNumber(wheel,value)
 7906 %  fluent(wheelNumber(wheel,value)).
 7907% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2272
 7908==> mpred_prop(wheelNumber(wheel,value),fluent).
 7909==> meta_argtypes(wheelNumber(wheel,value)).
 7910
 7911% noninertial WheelNumberDeterminer
 7912% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2273
 7913==> noninertial(wheelNumberDeterminer).
 7914
 7915% event Spin(dealer,wheel)
 7916 %  event(spin(dealer,wheel)).
 7917% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2275
 7918==> mpred_prop(spin(dealer,wheel),event).
 7919==> meta_argtypes(spin(dealer,wheel)).
 7920
 7921% event Reset(dealer,wheel)
 7922 %  event(reset(dealer,wheel)).
 7923% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2276
 7924==> mpred_prop(reset(dealer,wheel),event).
 7925==> meta_argtypes(reset(dealer,wheel)).
 7926
 7927
 7928% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2277
 7929% [wheel,time]
 7930% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2278
 7931% {value}% HoldsAt(WheelNumberDeterminer(wheel,value),time).
 7932
 7933 /*  exists([Value],
 7934          holds_at(wheelNumberDeterminer(Wheel,Value),
 7935   		Time)).
 7936 */
 7937
 7938 /*  holds_at(wheelNumberDeterminer(WheelNumberDeterminer_Param, Some_Param), Time4) :-
 7939       some(Some_Param,
 7940            '$kolem_Fn_353'(WheelNumberDeterminer_Param, Time4)).
 7941 */
 7942% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2279
 7943axiom(holds_at(wheelNumberDeterminer(WheelNumberDeterminer_Param, Some_Param), Time4),
 7944   
 7945    [ some(Some_Param,
 7946           '$kolem_Fn_353'(WheelNumberDeterminer_Param, Time4))
 7947    ]).
 7948
 7949 /*  not(some(Some_Param8, '$kolem_Fn_353'(Fn_353_Param, Time7))) :-
 7950       not(holds_at(wheelNumberDeterminer(Fn_353_Param, Some_Param8),
 7951                    Time7)).
 7952 */
 7953axiom(not(some(Some_Param8, '$kolem_Fn_353'(Fn_353_Param, Time7))),
 7954   
 7955    [ not(holds_at(wheelNumberDeterminer(Fn_353_Param, Some_Param8),
 7956                   Time7))
 7957    ]).
 7958
 7959
 7960% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2281
 7961% [wheel,value1,value2,time]
 7962% HoldsAt(WheelNumberDeterminer(wheel,value1),time) &
 7963% HoldsAt(WheelNumberDeterminer(wheel,value2),time) ->
 7964% value1=value2.
 7965% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2284
 7966axiom(Value1=Value2,
 7967   
 7968    [ holds_at(wheelNumberDeterminer(Wheel, Value1), Time),
 7969      holds_at(wheelNumberDeterminer(Wheel, Value2), Time)
 7970    ]).
 7971
 7972
 7973% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2286
 7974% [dealer,wheel,value,time]
 7975% HoldsAt(WheelNumberDeterminer(wheel,value),time) ->
 7976% Initiates(Spin(dealer,wheel),WheelNumber(wheel,value),time).
 7977% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2288
 7978axiom(initiates(spin(Dealer, Wheel), wheelNumber(Wheel, Value), Time),
 7979    [holds_at(wheelNumberDeterminer(Wheel, Value), Time)]).
 7980
 7981
 7982% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2290
 7983% [dealer,wheel,value1,value2,time]
 7984% HoldsAt(WheelNumber(wheel,value1),time) &
 7985% HoldsAt(WheelNumberDeterminer(wheel,value2),time) &
 7986% value1!=value2 ->
 7987% Terminates(Spin(dealer,wheel),WheelNumber(wheel,value1),time).
 7988% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2294
 7989axiom(terminates(spin(Dealer, Wheel), wheelNumber(Wheel, Value1), Time),
 7990   
 7991    [ holds_at(wheelNumber(Wheel, Value1), Time),
 7992      holds_at(wheelNumberDeterminer(Wheel, Value2), Time),
 7993      { dif(Value1, Value2)
 7994      }
 7995    ]).
 7996
 7997
 7998% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2296
 7999% [dealer,wheel,value,time]
 8000% Terminates(Reset(dealer,wheel),WheelNumber(wheel,value),time).
 8001% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2297
 8002axiom(terminates(reset(Dealer, Wheel), wheelNumber(Wheel, Value), Time),
 8003    []).
 8004
 8005
 8006% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2299
 8007% [wheel,value1,value2,time]
 8008% HoldsAt(WheelNumber(wheel,value1),time) &
 8009% HoldsAt(WheelNumber(wheel,value2),time) ->
 8010% value1=value2.
 8011% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2302
 8012axiom(Value1=Value2,
 8013   
 8014    [ holds_at(wheelNumber(Wheel, Value1), Time),
 8015      holds_at(wheelNumber(Wheel, Value2), Time)
 8016    ]).
 8017
 8018
 8019% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2304
 8020% [value]
 8021 % !HoldsAt(WheelNumber(Wheel1,value),0).
 8022 %  not(initially(wheelNumber(wheel1,Value))).
 8023axiom(not(initially(wheelNumber(wheel1, WheelNumber_Ret))),
 8024    []).
 8025
 8026
 8027% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2306
 8028% Happens(Spin(Dealer1,Wheel1),0).
 8029axiom(happens(spin(dealer1, wheel1), t),
 8030    [is_time(0)]).
 8031
 8032
 8033% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2307
 8034%;Happens(Reset(Dealer1,Wheel1),1).
 8035%; added to prune models
 8036
 8037
 8038% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2310
 8039% HoldsAt(WheelNumberDeterminer(Wheel1, 1),1).
 8040holds_at(wheelNumberDeterminer(wheel1,1),1).
 8041
 8042% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2312
 8043% completion Happens
 8044% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2313
 8045==> completion(happens).
 8046
 8047% range value 1 3
 8048% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2315
 8049==> range(value,1,3).
 8050
 8051% range time 0 1
 8052% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2316
 8053==> range(time,0,1).
 8054
 8055% range offset 1 1
 8056% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2317
 8057==> range(offset,1,1).
 8058%; End of file.
 8059%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 8060%; FILE: examples/Mueller2006/Chapter14/NetBill1.e
 8061%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 8062%;
 8063%; Copyright (c) 2005 IBM Corporation and others.
 8064%; All rights reserved. This program and the accompanying materials
 8065%; are made available under the terms of the Common Public License v1.0
 8066%; which accompanies this distribution, and is available at
 8067%; http://www.eclipse.org/legal/cpl-v10.html
 8068%;
 8069%; Contributors:
 8070%; IBM - Initial implementation
 8071%;
 8072%; @inproceedings{SirbuTygar:1995,
 8073%;   author = "Marvin A. Sirbu and J. D. Tygar",
 8074%;   year = "1995",
 8075%;   title = "Net\uppercase{B}ill: An \uppercase{I}nternet commerce system optimized for network delivered services",
 8076%;   editor = "
 8077%;   booktitle = "40th \uppercase{IEEE} \uppercase{C}omputer \uppercase{S}ociety \uppercase{I}nternational \uppercase{C}onference",
 8078%;   pages = "20--25",
 8079%;   publisher = "
 8080%;   address = "
 8081%; }
 8082%;
 8083%; @book{Mueller:2006,
 8084%;   author = "Erik T. Mueller",
 8085%;   year = "2006",
 8086%;   title = "Commonsense Reasoning",
 8087%;   address = "San Francisco",
 8088%;   publisher = "Morgan Kaufmann/Elsevier",
 8089%; }
 8090%;
 8091
 8092% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2355
 8093% option modeldiff on
 8094% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2356
 8095:- set_ec_option(modeldiff, on). 8096
 8097% load foundations/Root.e
 8098
 8099% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2358
 8100% load foundations/EC.e
 8101
 8102% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2360
 8103% sort agent
 8104% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2361
 8105==> sort(agent).
 8106
 8107% agent MusicStore, Jen
 8108% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2362
 8109==> t(agent,musicStore).
 8110==> t(agent,jen).
 8111
 8112% sort product
 8113% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2364
 8114==> sort(product).
 8115
 8116% product BritneyCD
 8117% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2365
 8118==> t(product,britneyCD).
 8119
 8120% sort f
 8121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2367
 8122==> sort(f).
 8123
 8124% f PurchaseRequestedJenMusicStoreBritneyCD1
 8125% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2368
 8126==> t(f,purchaseRequestedJenMusicStoreBritneyCD1).
 8127
 8128% f DeliveredMusicStoreJenBritneyCD
 8129% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2369
 8130==> t(f,deliveredMusicStoreJenBritneyCD).
 8131
 8132% f EPOSentJenMusicStore1
 8133% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2370
 8134==> t(f,ePOSentJenMusicStore1).
 8135
 8136% sort amount: integer
 8137% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2372
 8138==> subsort(amount,integer).
 8139
 8140% fluent C(agent,agent,f)
 8141 %  fluent(c(agent,agent,f)).
 8142% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2374
 8143==> mpred_prop(c(agent,agent,f),fluent).
 8144==> meta_argtypes(c(agent,agent,f)).
 8145
 8146% fluent CC(agent,agent,f,f)
 8147 %  fluent(cc(agent,agent,f,f)).
 8148% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2375
 8149==> mpred_prop(cc(agent,agent,f,f),fluent).
 8150==> meta_argtypes(cc(agent,agent,f,f)).
 8151
 8152% event CreateC(agent,agent,f)
 8153 %  event(createC(agent,agent,f)).
 8154% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2377
 8155==> mpred_prop(createC(agent,agent,f),event).
 8156==> meta_argtypes(createC(agent,agent,f)).
 8157
 8158% event CreateCC(agent,agent,f,f)
 8159 %  event(createCC(agent,agent,f,f)).
 8160% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2378
 8161==> mpred_prop(createCC(agent,agent,f,f),event).
 8162==> meta_argtypes(createCC(agent,agent,f,f)).
 8163
 8164% event DischargeC(agent,agent,f)
 8165 %  event(dischargeC(agent,agent,f)).
 8166% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2379
 8167==> mpred_prop(dischargeC(agent,agent,f),event).
 8168==> meta_argtypes(dischargeC(agent,agent,f)).
 8169
 8170% event DischargeCC(agent,agent,f,f)
 8171 %  event(dischargeCC(agent,agent,f,f)).
 8172% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2380
 8173==> mpred_prop(dischargeCC(agent,agent,f,f),event).
 8174==> meta_argtypes(dischargeCC(agent,agent,f,f)).
 8175
 8176% fluent QuoteSent(agent,agent,product,amount)
 8177 %  fluent(quoteSent(agent,agent,product,amount)).
 8178% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2382
 8179==> mpred_prop(quoteSent(agent,agent,product,amount),fluent).
 8180==> meta_argtypes(quoteSent(agent,agent,product,amount)).
 8181
 8182% fluent PurchaseRequested(agent,agent,product,amount)
 8183 %  fluent(purchaseRequested(agent,agent,product,amount)).
 8184% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2383
 8185==> mpred_prop(purchaseRequested(agent,agent,product,amount),fluent).
 8186==> meta_argtypes(purchaseRequested(agent,agent,product,amount)).
 8187
 8188% fluent Delivered(agent,agent,product)
 8189 %  fluent(delivered(agent,agent,product)).
 8190% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2384
 8191==> mpred_prop(delivered(agent,agent,product),fluent).
 8192==> meta_argtypes(delivered(agent,agent,product)).
 8193
 8194% fluent EPOSent(agent,agent,amount)
 8195 %  fluent(ePOSent(agent,agent,amount)).
 8196% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2385
 8197==> mpred_prop(ePOSent(agent,agent,amount),fluent).
 8198==> meta_argtypes(ePOSent(agent,agent,amount)).
 8199
 8200% event SendQuote(agent,agent,product,amount)
 8201 %  event(sendQuote(agent,agent,product,amount)).
 8202% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2387
 8203==> mpred_prop(sendQuote(agent,agent,product,amount),event).
 8204==> meta_argtypes(sendQuote(agent,agent,product,amount)).
 8205
 8206% event RequestPurchase(agent,agent,product,amount)
 8207 %  event(requestPurchase(agent,agent,product,amount)).
 8208% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2388
 8209==> mpred_prop(requestPurchase(agent,agent,product,amount),event).
 8210==> meta_argtypes(requestPurchase(agent,agent,product,amount)).
 8211
 8212% event Deliver(agent,agent,product)
 8213 %  event(deliver(agent,agent,product)).
 8214% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2389
 8215==> mpred_prop(deliver(agent,agent,product),event).
 8216==> meta_argtypes(deliver(agent,agent,product)).
 8217
 8218% event SendEPO(agent,agent,amount)
 8219 %  event(sendEPO(agent,agent,amount)).
 8220% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2390
 8221==> mpred_prop(sendEPO(agent,agent,amount),event).
 8222==> meta_argtypes(sendEPO(agent,agent,amount)).
 8223
 8224
 8225% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2391
 8226%; Sigma
 8227% [agent1,agent2,f,time]
 8228% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2394
 8229% Initiates(CreateC(agent1,agent2,f),C(agent1,agent2,f),time).
 8230axiom(initiates(createC(Agent1, Agent2, F), c(Agent1, Agent2, F), Time),
 8231    []).
 8232
 8233
 8234% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2396
 8235% [agent1,agent2,f1,f2,time]
 8236% Initiates(CreateCC(agent1,agent2,f1,f2),CC(agent1,agent2,f1,f2),time).
 8237% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2397
 8238axiom(initiates(createCC(Agent1, Agent2, F1, F2), cc(Agent1, Agent2, F1, F2), Time),
 8239    []).
 8240
 8241
 8242% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2399
 8243% [agent1,agent2,f,time]
 8244% Terminates(DischargeC(agent1,agent2,f),C(agent1,agent2,f),time).
 8245% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2400
 8246axiom(terminates(dischargeC(Agent1, Agent2, F), c(Agent1, Agent2, F), Time),
 8247    []).
 8248
 8249
 8250% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2402
 8251% [agent1,agent2,f1,f2,time]
 8252% Terminates(DischargeCC(agent1,agent2,f1,f2),CC(agent1,agent2,f1,f2),time).
 8253% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2403
 8254axiom(terminates(dischargeCC(Agent1, Agent2, F1, F2), cc(Agent1, Agent2, F1, F2), Time),
 8255    []).
 8256
 8257
 8258% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2405
 8259% [agent1,agent2,product,amount,time]
 8260% Initiates(SendQuote(agent1,agent2,product,amount),
 8261%           QuoteSent(agent1,agent2,product,amount),
 8262%           time).
 8263% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2408
 8264axiom(initiates(sendQuote(Agent1, Agent2, Product, Amount), quoteSent(Agent1, Agent2, Product, Amount), Time),
 8265    []).
 8266
 8267
 8268% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2410
 8269% [agent1,agent2,product,amount,time]
 8270% Initiates(RequestPurchase(agent1,agent2,product,amount),
 8271%           PurchaseRequested(agent1,agent2,product,amount),
 8272%           time).
 8273% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2413
 8274axiom(initiates(requestPurchase(Agent1, Agent2, Product, Amount), purchaseRequested(Agent1, Agent2, Product, Amount), Time),
 8275    []).
 8276
 8277
 8278% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2415
 8279% [agent1,agent2,product,time]
 8280% Initiates(Deliver(agent1,agent2,product),
 8281%           Delivered(agent1,agent2,product),
 8282%           time).
 8283% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2418
 8284axiom(initiates(deliver(Agent1, Agent2, Product), delivered(Agent1, Agent2, Product), Time),
 8285    []).
 8286
 8287
 8288% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2420
 8289% [agent1,agent2,amount,time]
 8290% Initiates(SendEPO(agent1,agent2,amount),
 8291%           EPOSent(agent1,agent2,amount),
 8292%           time).
 8293% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2423
 8294axiom(initiates(sendEPO(Agent1, Agent2, Amount), ePOSent(Agent1, Agent2, Amount), Time),
 8295    []).
 8296
 8297
 8298% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2425
 8299% [agent1,agent2,product,amount,f1,f2,time]
 8300% agent1=% MusicStore &
 8301% agent2=Jen &
 8302% product=BritneyCD &
 8303% amount=1 &
 8304% f1=PurchaseRequestedJenMusicStoreBritneyCD1 &
 8305% f2=DeliveredMusicStoreJenBritneyCD ->
 8306% Initiates(SendQuote(agent1,agent2,product,amount),
 8307%           CC(agent1,agent2,f1,f2),
 8308%           time).
 8309% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2434
 8310axiom(initiates(sendQuote(Agent1, Agent2, Product, Amount), cc(Agent1, Agent2, F1, F2), Time),
 8311   
 8312    [ equals(Agent1, musicStore),
 8313      equals(Agent2, jen),
 8314      equals(Product, britneyCD),
 8315      equals(Amount, 1),
 8316      equals(F1, purchaseRequestedJenMusicStoreBritneyCD1),
 8317      equals(F2, deliveredMusicStoreJenBritneyCD)
 8318    ]).
 8319
 8320
 8321% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2436
 8322% [agent1,agent2,product,amount,f1,f2,time]
 8323% agent1=% Jen &
 8324% agent2=MusicStore &
 8325% product=BritneyCD &
 8326% amount=1 &
 8327% f1=DeliveredMusicStoreJenBritneyCD &
 8328% f2=EPOSentJenMusicStore1 &
 8329% !HoldsAt(Delivered(agent2,agent1,product),time) ->
 8330% Initiates(RequestPurchase(agent1,agent2,product,amount),
 8331%           CC(agent1,agent2,f1,f2),
 8332%           time).
 8333% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2446
 8334axiom(initiates(requestPurchase(Agent1, Agent2, Product, Amount), cc(Agent1, Agent2, F1, F2), Time),
 8335   
 8336    [ equals(Agent1, jen),
 8337      equals(Agent2, musicStore),
 8338      equals(Product, britneyCD),
 8339      equals(Amount, 1),
 8340      equals(F1, deliveredMusicStoreJenBritneyCD),
 8341      equals(F2, ePOSentJenMusicStore1),
 8342      not(holds_at(delivered(Agent2, Agent1, Product),
 8343                   Time))
 8344    ]).
 8345
 8346
 8347% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2448
 8348%; Delta
 8349
 8350% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2450
 8351% Delta: 
 8352next_axiom_uses(delta).
 8353 
 8354
 8355
 8356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2450
 8357% [time]
 8358% HoldsAt(CC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time) &
 8359% HoldsAt(PurchaseRequested(Jen,MusicStore,BritneyCD,1),time) ->
 8360% Happens(CreateC(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time).
 8361% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2453
 8362axiom(happens(createC(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 8363   
 8364    [ holds_at(cc(musicStore,
 8365                  jen,
 8366                  purchaseRequestedJenMusicStoreBritneyCD1,
 8367                  deliveredMusicStoreJenBritneyCD),
 8368               Time),
 8369      holds_at(purchaseRequested(jen, musicStore, britneyCD, 1), Time)
 8370    ]).
 8371
 8372% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2455
 8373% Delta: 
 8374next_axiom_uses(delta).
 8375 
 8376
 8377
 8378% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2455
 8379% [time]
 8380% HoldsAt(CC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time) &
 8381% HoldsAt(PurchaseRequested(Jen, MusicStore, BritneyCD, 1),time) ->
 8382% Happens(DischargeCC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time).
 8383% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2458
 8384axiom(happens(dischargeCC(musicStore, jen, purchaseRequestedJenMusicStoreBritneyCD1, deliveredMusicStoreJenBritneyCD), Time),
 8385   
 8386    [ holds_at(cc(musicStore,
 8387                  jen,
 8388                  purchaseRequestedJenMusicStoreBritneyCD1,
 8389                  deliveredMusicStoreJenBritneyCD),
 8390               Time),
 8391      holds_at(purchaseRequested(jen, musicStore, britneyCD, 1), Time)
 8392    ]).
 8393
 8394% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2460
 8395% Delta: 
 8396next_axiom_uses(delta).
 8397 
 8398
 8399
 8400% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2460
 8401% [time]
 8402% HoldsAt(CC(Jen, MusicStore, DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time) &
 8403% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 8404% Happens(CreateC(Jen,MusicStore,EPOSentJenMusicStore1),time).
 8405% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2463
 8406axiom(happens(createC(jen, musicStore, ePOSentJenMusicStore1), Time),
 8407   
 8408    [ holds_at(cc(jen,
 8409                  musicStore,
 8410                  deliveredMusicStoreJenBritneyCD,
 8411                  ePOSentJenMusicStore1),
 8412               Time),
 8413      holds_at(delivered(musicStore, jen, britneyCD), Time)
 8414    ]).
 8415
 8416% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2465
 8417% Delta: 
 8418next_axiom_uses(delta).
 8419 
 8420
 8421
 8422% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2465
 8423% [time]
 8424% HoldsAt(CC(Jen, MusicStore, DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time) &
 8425% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 8426% Happens(DischargeCC(Jen,MusicStore,DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time).
 8427% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2468
 8428axiom(happens(dischargeCC(jen, musicStore, deliveredMusicStoreJenBritneyCD, ePOSentJenMusicStore1), Time),
 8429   
 8430    [ holds_at(cc(jen,
 8431                  musicStore,
 8432                  deliveredMusicStoreJenBritneyCD,
 8433                  ePOSentJenMusicStore1),
 8434               Time),
 8435      holds_at(delivered(musicStore, jen, britneyCD), Time)
 8436    ]).
 8437
 8438% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2470
 8439% Delta: 
 8440next_axiom_uses(delta).
 8441 
 8442
 8443
 8444% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2470
 8445% [time]
 8446% HoldsAt(C(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time) &
 8447% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 8448% Happens(DischargeC(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time).
 8449% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2473
 8450axiom(happens(dischargeC(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 8451   
 8452    [ holds_at(c(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 8453      holds_at(delivered(musicStore, jen, britneyCD), Time)
 8454    ]).
 8455
 8456% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2475
 8457% Delta: 
 8458next_axiom_uses(delta).
 8459 
 8460
 8461
 8462% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2475
 8463% [time]
 8464% HoldsAt(C(Jen,MusicStore,EPOSentJenMusicStore1),time) &
 8465% HoldsAt(EPOSent(Jen,MusicStore,1),time) ->
 8466% Happens(DischargeC(Jen,MusicStore,EPOSentJenMusicStore1),time).
 8467% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2478
 8468axiom(happens(dischargeC(jen, musicStore, ePOSentJenMusicStore1), Time),
 8469   
 8470    [ holds_at(c(jen, musicStore, ePOSentJenMusicStore1), Time),
 8471      holds_at(ePOSent(jen, musicStore, 1), Time)
 8472    ]).
 8473
 8474% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2480
 8475% Delta: 
 8476next_axiom_uses(delta).
 8477 
 8478
 8479
 8480% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2480
 8481% Happens(SendQuote(MusicStore,Jen,BritneyCD,1),0).
 8482axiom(happens(sendQuote(musicStore, jen, britneyCD, 1), t),
 8483    [is_time(0)]).
 8484
 8485% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2481
 8486% Delta: 
 8487next_axiom_uses(delta).
 8488 
 8489
 8490
 8491% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2481
 8492% Happens(RequestPurchase(Jen,MusicStore,BritneyCD,1),1).
 8493axiom(happens(requestPurchase(jen, musicStore, britneyCD, 1), start),
 8494    [is_time(1), b(t, start), ignore(t+1=start)]).
 8495
 8496% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2482
 8497% Delta: 
 8498next_axiom_uses(delta).
 8499 
 8500
 8501
 8502% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2482
 8503% Happens(Deliver(MusicStore,Jen,BritneyCD),3).
 8504axiom(happens(deliver(musicStore, jen, britneyCD), t3),
 8505    [is_time(3), b(t, t3), ignore(t+3=t3)]).
 8506
 8507% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2483
 8508% Delta: 
 8509next_axiom_uses(delta).
 8510 
 8511
 8512
 8513% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2483
 8514% Happens(SendEPO(Jen,MusicStore,1),5).
 8515axiom(happens(sendEPO(jen, musicStore, 1), t5),
 8516    [is_time(5), b(t, t5), ignore(t+5=t5)]).
 8517
 8518
 8519% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2485
 8520%; Gamma
 8521% [agent1,agent2,product,amount]
 8522% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2488
 8523% !HoldsAt(QuoteSent(agent1,agent2,product,amount),0).
 8524
 8525 /*  not(initially(quoteSent(Agent1,
 8526   			Agent2,
 8527   			Product,
 8528   			Amount))).
 8529 */
 8530axiom(not(initially(quoteSent(QuoteSent_Param, _, _, QuoteSent_Ret))),
 8531    []).
 8532
 8533
 8534% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2490
 8535% [agent1,agent2,product,amount]
 8536% !HoldsAt(PurchaseRequested(agent1,agent2,product,amount),0).
 8537
 8538 /*  not(initially(purchaseRequested(Agent1,
 8539   				Agent2,
 8540   				Product,
 8541   				Amount))).
 8542 */
 8543% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2491
 8544axiom(not(initially(purchaseRequested(PurchaseRequested_Param, _, _, PurchaseRequested_Ret))),
 8545    []).
 8546
 8547
 8548% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2493
 8549% [agent1,agent2,product]
 8550% !HoldsAt(Delivered(agent1,agent2,product),0).
 8551 %  not(initially(delivered(Agent1,Agent2,Product))).
 8552% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2494
 8553axiom(not(initially(delivered(Delivered_Param, _, Delivered_Ret))),
 8554    []).
 8555
 8556
 8557% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2496
 8558% [agent1,agent2,f]
 8559% !HoldsAt(C(agent1,agent2,f),0).
 8560 %  not(initially(c(Agent1,Agent2,F))).
 8561% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2497
 8562axiom(not(initially(c(C_Param, _, C_Ret))),
 8563    []).
 8564
 8565
 8566% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2499
 8567% [agent1,agent2,f1,f2]
 8568% !HoldsAt(CC(agent1,agent2,f1,f2),0).
 8569 %  not(initially(cc(Agent1,Agent2,F1,F2))).
 8570% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2500
 8571axiom(not(initially(cc(Cc_Param, _, _, Cc_Ret))),
 8572    []).
 8573
 8574
 8575% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2502
 8576% [agent1,agent2,amount]
 8577% !HoldsAt(EPOSent(agent1,agent2,amount),0).
 8578 %  not(initially(ePOSent(Agent1,Agent2,Amount))).
 8579% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2503
 8580axiom(not(initially(ePOSent(EPOSent_Param, _, EPOSent_Ret))),
 8581    []).
 8582
 8583% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2505
 8584% completion Delta Happens
 8585% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2506
 8586==> completion(delta).
 8587==> completion(happens).
 8588
 8589% range time 0 7
 8590% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2508
 8591==> range(time,0,7).
 8592
 8593% range offset 1 1
 8594% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2509
 8595==> range(offset,1,1).
 8596
 8597% range amount 1 1
 8598% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2510
 8599==> range(amount,1,1).
 8600%; End of file.
 8601%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 8602%; FILE: examples/Mueller2006/Chapter14/NetBill3.e
 8603%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 8604%;
 8605%; Copyright (c) 2005 IBM Corporation and others.
 8606%; All rights reserved. This program and the accompanying materials
 8607%; are made available under the terms of the Common Public License v1.0
 8608%; which accompanies this distribution, and is available at
 8609%; http://www.eclipse.org/legal/cpl-v10.html
 8610%;
 8611%; Contributors:
 8612%; IBM - Initial implementation
 8613%;
 8614%; @inproceedings{SirbuTygar:1995,
 8615%;   author = "Marvin A. Sirbu and J. D. Tygar",
 8616%;   year = "1995",
 8617%;   title = "Net\uppercase{B}ill: An \uppercase{I}nternet commerce system optimized for network delivered services",
 8618%;   editor = "
 8619%;   booktitle = "40th \uppercase{IEEE} \uppercase{C}omputer \uppercase{S}ociety \uppercase{I}nternational \uppercase{C}onference",
 8620%;   pages = "20--25",
 8621%;   publisher = "
 8622%;   address = "
 8623%; }
 8624%;
 8625%; @book{Mueller:2006,
 8626%;   author = "Erik T. Mueller",
 8627%;   year = "2006",
 8628%;   title = "Commonsense Reasoning",
 8629%;   address = "San Francisco",
 8630%;   publisher = "Morgan Kaufmann/Elsevier",
 8631%; }
 8632%;
 8633
 8634% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2548
 8635% option modeldiff on
 8636% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2549
 8637:- set_ec_option(modeldiff, on). 8638
 8639% load foundations/Root.e
 8640
 8641% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2551
 8642% load foundations/EC.e
 8643
 8644% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2553
 8645% sort agent
 8646% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2554
 8647==> sort(agent).
 8648
 8649% agent MusicStore, Jen
 8650% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2555
 8651==> t(agent,musicStore).
 8652==> t(agent,jen).
 8653
 8654% sort product
 8655% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2557
 8656==> sort(product).
 8657
 8658% product BritneyCD
 8659% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2558
 8660==> t(product,britneyCD).
 8661
 8662% sort f
 8663% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2560
 8664==> sort(f).
 8665
 8666% f PurchaseRequestedJenMusicStoreBritneyCD1
 8667% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2561
 8668==> t(f,purchaseRequestedJenMusicStoreBritneyCD1).
 8669
 8670% f DeliveredMusicStoreJenBritneyCD
 8671% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2562
 8672==> t(f,deliveredMusicStoreJenBritneyCD).
 8673
 8674% f EPOSentJenMusicStore1
 8675% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2563
 8676==> t(f,ePOSentJenMusicStore1).
 8677
 8678% sort amount: integer
 8679% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2565
 8680==> subsort(amount,integer).
 8681
 8682% fluent C(agent,agent,f)
 8683 %  fluent(c(agent,agent,f)).
 8684% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2567
 8685==> mpred_prop(c(agent,agent,f),fluent).
 8686==> meta_argtypes(c(agent,agent,f)).
 8687
 8688% fluent CC(agent,agent,f,f)
 8689 %  fluent(cc(agent,agent,f,f)).
 8690% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2568
 8691==> mpred_prop(cc(agent,agent,f,f),fluent).
 8692==> meta_argtypes(cc(agent,agent,f,f)).
 8693
 8694% event CreateC(agent,agent,f)
 8695 %  event(createC(agent,agent,f)).
 8696% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2570
 8697==> mpred_prop(createC(agent,agent,f),event).
 8698==> meta_argtypes(createC(agent,agent,f)).
 8699
 8700% event CreateCC(agent,agent,f,f)
 8701 %  event(createCC(agent,agent,f,f)).
 8702% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2571
 8703==> mpred_prop(createCC(agent,agent,f,f),event).
 8704==> meta_argtypes(createCC(agent,agent,f,f)).
 8705
 8706% event DischargeC(agent,agent,f)
 8707 %  event(dischargeC(agent,agent,f)).
 8708% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2572
 8709==> mpred_prop(dischargeC(agent,agent,f),event).
 8710==> meta_argtypes(dischargeC(agent,agent,f)).
 8711
 8712% event DischargeCC(agent,agent,f,f)
 8713 %  event(dischargeCC(agent,agent,f,f)).
 8714% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2573
 8715==> mpred_prop(dischargeCC(agent,agent,f,f),event).
 8716==> meta_argtypes(dischargeCC(agent,agent,f,f)).
 8717
 8718% fluent QuoteSent(agent,agent,product,amount)
 8719 %  fluent(quoteSent(agent,agent,product,amount)).
 8720% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2575
 8721==> mpred_prop(quoteSent(agent,agent,product,amount),fluent).
 8722==> meta_argtypes(quoteSent(agent,agent,product,amount)).
 8723
 8724% fluent PurchaseRequested(agent,agent,product,amount)
 8725 %  fluent(purchaseRequested(agent,agent,product,amount)).
 8726% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2576
 8727==> mpred_prop(purchaseRequested(agent,agent,product,amount),fluent).
 8728==> meta_argtypes(purchaseRequested(agent,agent,product,amount)).
 8729
 8730% fluent Delivered(agent,agent,product)
 8731 %  fluent(delivered(agent,agent,product)).
 8732% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2577
 8733==> mpred_prop(delivered(agent,agent,product),fluent).
 8734==> meta_argtypes(delivered(agent,agent,product)).
 8735
 8736% fluent EPOSent(agent,agent,amount)
 8737 %  fluent(ePOSent(agent,agent,amount)).
 8738% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2578
 8739==> mpred_prop(ePOSent(agent,agent,amount),fluent).
 8740==> meta_argtypes(ePOSent(agent,agent,amount)).
 8741
 8742% event SendQuote(agent,agent,product,amount)
 8743 %  event(sendQuote(agent,agent,product,amount)).
 8744% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2580
 8745==> mpred_prop(sendQuote(agent,agent,product,amount),event).
 8746==> meta_argtypes(sendQuote(agent,agent,product,amount)).
 8747
 8748% event RequestPurchase(agent,agent,product,amount)
 8749 %  event(requestPurchase(agent,agent,product,amount)).
 8750% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2581
 8751==> mpred_prop(requestPurchase(agent,agent,product,amount),event).
 8752==> meta_argtypes(requestPurchase(agent,agent,product,amount)).
 8753
 8754% event Deliver(agent,agent,product)
 8755 %  event(deliver(agent,agent,product)).
 8756% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2582
 8757==> mpred_prop(deliver(agent,agent,product),event).
 8758==> meta_argtypes(deliver(agent,agent,product)).
 8759
 8760% event SendEPO(agent,agent,amount)
 8761 %  event(sendEPO(agent,agent,amount)).
 8762% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2583
 8763==> mpred_prop(sendEPO(agent,agent,amount),event).
 8764==> meta_argtypes(sendEPO(agent,agent,amount)).
 8765
 8766
 8767% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2584
 8768%; Sigma
 8769% [agent1,agent2,f,time]
 8770% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2587
 8771% Initiates(CreateC(agent1,agent2,f),C(agent1,agent2,f),time).
 8772axiom(initiates(createC(Agent1, Agent2, F), c(Agent1, Agent2, F), Time),
 8773    []).
 8774
 8775
 8776% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2589
 8777% [agent1,agent2,f1,f2,time]
 8778% Initiates(CreateCC(agent1,agent2,f1,f2),CC(agent1,agent2,f1,f2),time).
 8779% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2590
 8780axiom(initiates(createCC(Agent1, Agent2, F1, F2), cc(Agent1, Agent2, F1, F2), Time),
 8781    []).
 8782
 8783
 8784% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2592
 8785% [agent1,agent2,f,time]
 8786% Terminates(DischargeC(agent1,agent2,f),C(agent1,agent2,f),time).
 8787% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2593
 8788axiom(terminates(dischargeC(Agent1, Agent2, F), c(Agent1, Agent2, F), Time),
 8789    []).
 8790
 8791
 8792% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2595
 8793% [agent1,agent2,f1,f2,time]
 8794% Terminates(DischargeCC(agent1,agent2,f1,f2),CC(agent1,agent2,f1,f2),time).
 8795% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2596
 8796axiom(terminates(dischargeCC(Agent1, Agent2, F1, F2), cc(Agent1, Agent2, F1, F2), Time),
 8797    []).
 8798
 8799
 8800% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2598
 8801% [agent1,agent2,product,amount,time]
 8802% Initiates(SendQuote(agent1,agent2,product,amount),
 8803%           QuoteSent(agent1,agent2,product,amount),
 8804%           time).
 8805% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2601
 8806axiom(initiates(sendQuote(Agent1, Agent2, Product, Amount), quoteSent(Agent1, Agent2, Product, Amount), Time),
 8807    []).
 8808
 8809
 8810% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2603
 8811% [agent1,agent2,product,amount,time]
 8812% Initiates(RequestPurchase(agent1,agent2,product,amount),
 8813%           PurchaseRequested(agent1,agent2,product,amount),
 8814%           time).
 8815% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2606
 8816axiom(initiates(requestPurchase(Agent1, Agent2, Product, Amount), purchaseRequested(Agent1, Agent2, Product, Amount), Time),
 8817    []).
 8818
 8819
 8820% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2608
 8821% [agent1,agent2,product,time]
 8822% Initiates(Deliver(agent1,agent2,product),
 8823%           Delivered(agent1,agent2,product),
 8824%           time).
 8825% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2611
 8826axiom(initiates(deliver(Agent1, Agent2, Product), delivered(Agent1, Agent2, Product), Time),
 8827    []).
 8828
 8829
 8830% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2613
 8831% [agent1,agent2,amount,time]
 8832% Initiates(SendEPO(agent1,agent2,amount),
 8833%           EPOSent(agent1,agent2,amount),
 8834%           time).
 8835% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2616
 8836axiom(initiates(sendEPO(Agent1, Agent2, Amount), ePOSent(Agent1, Agent2, Amount), Time),
 8837    []).
 8838
 8839
 8840% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2618
 8841% [agent1,agent2,product,amount,f1,f2,time]
 8842% agent1=% MusicStore &
 8843% agent2=Jen &
 8844% product=BritneyCD &
 8845% amount=1 &
 8846% f1=PurchaseRequestedJenMusicStoreBritneyCD1 &
 8847% f2=DeliveredMusicStoreJenBritneyCD ->
 8848% Initiates(SendQuote(agent1,agent2,product,amount),
 8849%           CC(agent1,agent2,f1,f2),
 8850%           time).
 8851% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2627
 8852axiom(initiates(sendQuote(Agent1, Agent2, Product, Amount), cc(Agent1, Agent2, F1, F2), Time),
 8853   
 8854    [ equals(Agent1, musicStore),
 8855      equals(Agent2, jen),
 8856      equals(Product, britneyCD),
 8857      equals(Amount, 1),
 8858      equals(F1, purchaseRequestedJenMusicStoreBritneyCD1),
 8859      equals(F2, deliveredMusicStoreJenBritneyCD)
 8860    ]).
 8861
 8862
 8863% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2629
 8864% [agent1,agent2,product,amount,f1,f2,time]
 8865% agent1=% Jen &
 8866% agent2=MusicStore &
 8867% product=BritneyCD &
 8868% amount=1 &
 8869% f1=DeliveredMusicStoreJenBritneyCD &
 8870% f2=EPOSentJenMusicStore1 &
 8871% !HoldsAt(Delivered(agent2,agent1,product),time) ->
 8872% Initiates(RequestPurchase(agent1,agent2,product,amount),
 8873%           CC(agent1,agent2,f1,f2),
 8874%           time).
 8875% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2639
 8876axiom(initiates(requestPurchase(Agent1, Agent2, Product, Amount), cc(Agent1, Agent2, F1, F2), Time),
 8877   
 8878    [ equals(Agent1, jen),
 8879      equals(Agent2, musicStore),
 8880      equals(Product, britneyCD),
 8881      equals(Amount, 1),
 8882      equals(F1, deliveredMusicStoreJenBritneyCD),
 8883      equals(F2, ePOSentJenMusicStore1),
 8884      not(holds_at(delivered(Agent2, Agent1, Product),
 8885                   Time))
 8886    ]).
 8887
 8888
 8889% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2641
 8890%; Delta
 8891
 8892% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2643
 8893% Delta: 
 8894next_axiom_uses(delta).
 8895 
 8896
 8897
 8898% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2643
 8899% [time]
 8900% HoldsAt(CC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time) &
 8901% HoldsAt(PurchaseRequested(Jen,MusicStore,BritneyCD,1),time) ->
 8902% Happens(CreateC(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time).
 8903% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2646
 8904axiom(happens(createC(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 8905   
 8906    [ holds_at(cc(musicStore,
 8907                  jen,
 8908                  purchaseRequestedJenMusicStoreBritneyCD1,
 8909                  deliveredMusicStoreJenBritneyCD),
 8910               Time),
 8911      holds_at(purchaseRequested(jen, musicStore, britneyCD, 1), Time)
 8912    ]).
 8913
 8914% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2648
 8915% Delta: 
 8916next_axiom_uses(delta).
 8917 
 8918
 8919
 8920% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2648
 8921% [time]
 8922% HoldsAt(CC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time) &
 8923% HoldsAt(PurchaseRequested(Jen, MusicStore, BritneyCD, 1),time) ->
 8924% Happens(DischargeCC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time).
 8925% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2651
 8926axiom(happens(dischargeCC(musicStore, jen, purchaseRequestedJenMusicStoreBritneyCD1, deliveredMusicStoreJenBritneyCD), Time),
 8927   
 8928    [ holds_at(cc(musicStore,
 8929                  jen,
 8930                  purchaseRequestedJenMusicStoreBritneyCD1,
 8931                  deliveredMusicStoreJenBritneyCD),
 8932               Time),
 8933      holds_at(purchaseRequested(jen, musicStore, britneyCD, 1), Time)
 8934    ]).
 8935
 8936% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2653
 8937% Delta: 
 8938next_axiom_uses(delta).
 8939 
 8940
 8941
 8942% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2653
 8943% [time]
 8944% HoldsAt(CC(Jen, MusicStore, DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time) &
 8945% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 8946% Happens(CreateC(Jen,MusicStore,EPOSentJenMusicStore1),time).
 8947% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2656
 8948axiom(happens(createC(jen, musicStore, ePOSentJenMusicStore1), Time),
 8949   
 8950    [ holds_at(cc(jen,
 8951                  musicStore,
 8952                  deliveredMusicStoreJenBritneyCD,
 8953                  ePOSentJenMusicStore1),
 8954               Time),
 8955      holds_at(delivered(musicStore, jen, britneyCD), Time)
 8956    ]).
 8957
 8958% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2658
 8959% Delta: 
 8960next_axiom_uses(delta).
 8961 
 8962
 8963
 8964% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2658
 8965% [time]
 8966% HoldsAt(CC(Jen, MusicStore, DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time) &
 8967% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 8968% Happens(DischargeCC(Jen,MusicStore,DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time).
 8969% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2661
 8970axiom(happens(dischargeCC(jen, musicStore, deliveredMusicStoreJenBritneyCD, ePOSentJenMusicStore1), Time),
 8971   
 8972    [ holds_at(cc(jen,
 8973                  musicStore,
 8974                  deliveredMusicStoreJenBritneyCD,
 8975                  ePOSentJenMusicStore1),
 8976               Time),
 8977      holds_at(delivered(musicStore, jen, britneyCD), Time)
 8978    ]).
 8979
 8980% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2663
 8981% Delta: 
 8982next_axiom_uses(delta).
 8983 
 8984
 8985
 8986% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2663
 8987% [time]
 8988% HoldsAt(C(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time) &
 8989% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 8990% Happens(DischargeC(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time).
 8991% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2666
 8992axiom(happens(dischargeC(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 8993   
 8994    [ holds_at(c(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 8995      holds_at(delivered(musicStore, jen, britneyCD), Time)
 8996    ]).
 8997
 8998% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2668
 8999% Delta: 
 9000next_axiom_uses(delta).
 9001 
 9002
 9003
 9004% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2668
 9005% [time]
 9006% HoldsAt(C(Jen,MusicStore,EPOSentJenMusicStore1),time) &
 9007% HoldsAt(EPOSent(Jen,MusicStore,1),time) ->
 9008% Happens(DischargeC(Jen,MusicStore,EPOSentJenMusicStore1),time).
 9009% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2671
 9010axiom(happens(dischargeC(jen, musicStore, ePOSentJenMusicStore1), Time),
 9011   
 9012    [ holds_at(c(jen, musicStore, ePOSentJenMusicStore1), Time),
 9013      holds_at(ePOSent(jen, musicStore, 1), Time)
 9014    ]).
 9015
 9016% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2673
 9017% Delta: 
 9018next_axiom_uses(delta).
 9019 
 9020
 9021
 9022% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2673
 9023% Happens(Deliver(MusicStore,Jen,BritneyCD),0).
 9024axiom(happens(deliver(musicStore, jen, britneyCD), t),
 9025    [is_time(0)]).
 9026
 9027% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2674
 9028% Delta: 
 9029next_axiom_uses(delta).
 9030 
 9031
 9032
 9033% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2674
 9034% Happens(SendEPO(Jen,MusicStore,1),2).
 9035axiom(happens(sendEPO(jen, musicStore, 1), t2),
 9036    [is_time(2), b(t, t2), ignore(t+2=t2)]).
 9037
 9038
 9039% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2676
 9040%; Gamma
 9041% [agent1,agent2,product,amount]
 9042% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2679
 9043% !HoldsAt(QuoteSent(agent1,agent2,product,amount),0).
 9044
 9045 /*  not(initially(quoteSent(Agent1,
 9046   			Agent2,
 9047   			Product,
 9048   			Amount))).
 9049 */
 9050axiom(not(initially(quoteSent(QuoteSent_Param, _, _, QuoteSent_Ret))),
 9051    []).
 9052
 9053
 9054% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2681
 9055% [agent1,agent2,product,amount]
 9056% !HoldsAt(PurchaseRequested(agent1,agent2,product,amount),0).
 9057
 9058 /*  not(initially(purchaseRequested(Agent1,
 9059   				Agent2,
 9060   				Product,
 9061   				Amount))).
 9062 */
 9063% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2682
 9064axiom(not(initially(purchaseRequested(PurchaseRequested_Param, _, _, PurchaseRequested_Ret))),
 9065    []).
 9066
 9067
 9068% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2684
 9069% [agent1,agent2,product]
 9070% !HoldsAt(Delivered(agent1,agent2,product),0).
 9071 %  not(initially(delivered(Agent1,Agent2,Product))).
 9072% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2685
 9073axiom(not(initially(delivered(Delivered_Param, _, Delivered_Ret))),
 9074    []).
 9075
 9076
 9077% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2687
 9078% [agent1,agent2,f]
 9079% !HoldsAt(C(agent1,agent2,f),0).
 9080 %  not(initially(c(Agent1,Agent2,F))).
 9081% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2688
 9082axiom(not(initially(c(C_Param, _, C_Ret))),
 9083    []).
 9084
 9085
 9086% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2690
 9087% [agent1,agent2,f1,f2]
 9088% !HoldsAt(CC(agent1,agent2,f1,f2),0).
 9089 %  not(initially(cc(Agent1,Agent2,F1,F2))).
 9090% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2691
 9091axiom(not(initially(cc(Cc_Param, _, _, Cc_Ret))),
 9092    []).
 9093
 9094
 9095% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2693
 9096% [agent1,agent2,amount]
 9097% !HoldsAt(EPOSent(agent1,agent2,amount),0).
 9098 %  not(initially(ePOSent(Agent1,Agent2,Amount))).
 9099% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2694
 9100axiom(not(initially(ePOSent(EPOSent_Param, _, EPOSent_Ret))),
 9101    []).
 9102
 9103% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2696
 9104% completion Delta Happens
 9105% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2697
 9106==> completion(delta).
 9107==> completion(happens).
 9108
 9109% range time 0 4
 9110% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2699
 9111==> range(time,0,4).
 9112
 9113% range offset 1 1
 9114% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2700
 9115==> range(offset,1,1).
 9116
 9117% range amount 1 1
 9118% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2701
 9119==> range(amount,1,1).
 9120%; End of file.
 9121%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 9122%; FILE: examples/Mueller2006/Chapter14/NetBill2.e
 9123%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 9124%;
 9125%; Copyright (c) 2005 IBM Corporation and others.
 9126%; All rights reserved. This program and the accompanying materials
 9127%; are made available under the terms of the Common Public License v1.0
 9128%; which accompanies this distribution, and is available at
 9129%; http://www.eclipse.org/legal/cpl-v10.html
 9130%;
 9131%; Contributors:
 9132%; IBM - Initial implementation
 9133%;
 9134%; @inproceedings{SirbuTygar:1995,
 9135%;   author = "Marvin A. Sirbu and J. D. Tygar",
 9136%;   year = "1995",
 9137%;   title = "Net\uppercase{B}ill: An \uppercase{I}nternet commerce system optimized for network delivered services",
 9138%;   editor = "
 9139%;   booktitle = "40th \uppercase{IEEE} \uppercase{C}omputer \uppercase{S}ociety \uppercase{I}nternational \uppercase{C}onference",
 9140%;   pages = "20--25",
 9141%;   publisher = "
 9142%;   address = "
 9143%; }
 9144%;
 9145%; @book{Mueller:2006,
 9146%;   author = "Erik T. Mueller",
 9147%;   year = "2006",
 9148%;   title = "Commonsense Reasoning",
 9149%;   address = "San Francisco",
 9150%;   publisher = "Morgan Kaufmann/Elsevier",
 9151%; }
 9152%;
 9153
 9154% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2739
 9155% option modeldiff on
 9156% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2740
 9157:- set_ec_option(modeldiff, on). 9158
 9159% load foundations/Root.e
 9160
 9161% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2742
 9162% load foundations/EC.e
 9163
 9164% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2744
 9165% sort agent
 9166% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2745
 9167==> sort(agent).
 9168
 9169% agent MusicStore, Jen
 9170% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2746
 9171==> t(agent,musicStore).
 9172==> t(agent,jen).
 9173
 9174% sort product
 9175% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2748
 9176==> sort(product).
 9177
 9178% product BritneyCD
 9179% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2749
 9180==> t(product,britneyCD).
 9181
 9182% sort f
 9183% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2751
 9184==> sort(f).
 9185
 9186% f PurchaseRequestedJenMusicStoreBritneyCD1
 9187% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2752
 9188==> t(f,purchaseRequestedJenMusicStoreBritneyCD1).
 9189
 9190% f DeliveredMusicStoreJenBritneyCD
 9191% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2753
 9192==> t(f,deliveredMusicStoreJenBritneyCD).
 9193
 9194% f EPOSentJenMusicStore1
 9195% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2754
 9196==> t(f,ePOSentJenMusicStore1).
 9197
 9198% sort amount: integer
 9199% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2756
 9200==> subsort(amount,integer).
 9201
 9202% fluent C(agent,agent,f)
 9203 %  fluent(c(agent,agent,f)).
 9204% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2758
 9205==> mpred_prop(c(agent,agent,f),fluent).
 9206==> meta_argtypes(c(agent,agent,f)).
 9207
 9208% fluent CC(agent,agent,f,f)
 9209 %  fluent(cc(agent,agent,f,f)).
 9210% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2759
 9211==> mpred_prop(cc(agent,agent,f,f),fluent).
 9212==> meta_argtypes(cc(agent,agent,f,f)).
 9213
 9214% event CreateC(agent,agent,f)
 9215 %  event(createC(agent,agent,f)).
 9216% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2761
 9217==> mpred_prop(createC(agent,agent,f),event).
 9218==> meta_argtypes(createC(agent,agent,f)).
 9219
 9220% event CreateCC(agent,agent,f,f)
 9221 %  event(createCC(agent,agent,f,f)).
 9222% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2762
 9223==> mpred_prop(createCC(agent,agent,f,f),event).
 9224==> meta_argtypes(createCC(agent,agent,f,f)).
 9225
 9226% event DischargeC(agent,agent,f)
 9227 %  event(dischargeC(agent,agent,f)).
 9228% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2763
 9229==> mpred_prop(dischargeC(agent,agent,f),event).
 9230==> meta_argtypes(dischargeC(agent,agent,f)).
 9231
 9232% event DischargeCC(agent,agent,f,f)
 9233 %  event(dischargeCC(agent,agent,f,f)).
 9234% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2764
 9235==> mpred_prop(dischargeCC(agent,agent,f,f),event).
 9236==> meta_argtypes(dischargeCC(agent,agent,f,f)).
 9237
 9238% fluent QuoteSent(agent,agent,product,amount)
 9239 %  fluent(quoteSent(agent,agent,product,amount)).
 9240% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2766
 9241==> mpred_prop(quoteSent(agent,agent,product,amount),fluent).
 9242==> meta_argtypes(quoteSent(agent,agent,product,amount)).
 9243
 9244% fluent PurchaseRequested(agent,agent,product,amount)
 9245 %  fluent(purchaseRequested(agent,agent,product,amount)).
 9246% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2767
 9247==> mpred_prop(purchaseRequested(agent,agent,product,amount),fluent).
 9248==> meta_argtypes(purchaseRequested(agent,agent,product,amount)).
 9249
 9250% fluent Delivered(agent,agent,product)
 9251 %  fluent(delivered(agent,agent,product)).
 9252% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2768
 9253==> mpred_prop(delivered(agent,agent,product),fluent).
 9254==> meta_argtypes(delivered(agent,agent,product)).
 9255
 9256% fluent EPOSent(agent,agent,amount)
 9257 %  fluent(ePOSent(agent,agent,amount)).
 9258% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2769
 9259==> mpred_prop(ePOSent(agent,agent,amount),fluent).
 9260==> meta_argtypes(ePOSent(agent,agent,amount)).
 9261
 9262% event SendQuote(agent,agent,product,amount)
 9263 %  event(sendQuote(agent,agent,product,amount)).
 9264% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2771
 9265==> mpred_prop(sendQuote(agent,agent,product,amount),event).
 9266==> meta_argtypes(sendQuote(agent,agent,product,amount)).
 9267
 9268% event RequestPurchase(agent,agent,product,amount)
 9269 %  event(requestPurchase(agent,agent,product,amount)).
 9270% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2772
 9271==> mpred_prop(requestPurchase(agent,agent,product,amount),event).
 9272==> meta_argtypes(requestPurchase(agent,agent,product,amount)).
 9273
 9274% event Deliver(agent,agent,product)
 9275 %  event(deliver(agent,agent,product)).
 9276% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2773
 9277==> mpred_prop(deliver(agent,agent,product),event).
 9278==> meta_argtypes(deliver(agent,agent,product)).
 9279
 9280% event SendEPO(agent,agent,amount)
 9281 %  event(sendEPO(agent,agent,amount)).
 9282% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2774
 9283==> mpred_prop(sendEPO(agent,agent,amount),event).
 9284==> meta_argtypes(sendEPO(agent,agent,amount)).
 9285
 9286
 9287% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2775
 9288%; Sigma
 9289% [agent1,agent2,f,time]
 9290% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2778
 9291% Initiates(CreateC(agent1,agent2,f),C(agent1,agent2,f),time).
 9292axiom(initiates(createC(Agent1, Agent2, F), c(Agent1, Agent2, F), Time),
 9293    []).
 9294
 9295
 9296% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2780
 9297% [agent1,agent2,f1,f2,time]
 9298% Initiates(CreateCC(agent1,agent2,f1,f2),CC(agent1,agent2,f1,f2),time).
 9299% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2781
 9300axiom(initiates(createCC(Agent1, Agent2, F1, F2), cc(Agent1, Agent2, F1, F2), Time),
 9301    []).
 9302
 9303
 9304% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2783
 9305% [agent1,agent2,f,time]
 9306% Terminates(DischargeC(agent1,agent2,f),C(agent1,agent2,f),time).
 9307% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2784
 9308axiom(terminates(dischargeC(Agent1, Agent2, F), c(Agent1, Agent2, F), Time),
 9309    []).
 9310
 9311
 9312% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2786
 9313% [agent1,agent2,f1,f2,time]
 9314% Terminates(DischargeCC(agent1,agent2,f1,f2),CC(agent1,agent2,f1,f2),time).
 9315% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2787
 9316axiom(terminates(dischargeCC(Agent1, Agent2, F1, F2), cc(Agent1, Agent2, F1, F2), Time),
 9317    []).
 9318
 9319
 9320% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2789
 9321% [agent1,agent2,product,amount,time]
 9322% Initiates(SendQuote(agent1,agent2,product,amount),
 9323%           QuoteSent(agent1,agent2,product,amount),
 9324%           time).
 9325% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2792
 9326axiom(initiates(sendQuote(Agent1, Agent2, Product, Amount), quoteSent(Agent1, Agent2, Product, Amount), Time),
 9327    []).
 9328
 9329
 9330% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2794
 9331% [agent1,agent2,product,amount,time]
 9332% Initiates(RequestPurchase(agent1,agent2,product,amount),
 9333%           PurchaseRequested(agent1,agent2,product,amount),
 9334%           time).
 9335% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2797
 9336axiom(initiates(requestPurchase(Agent1, Agent2, Product, Amount), purchaseRequested(Agent1, Agent2, Product, Amount), Time),
 9337    []).
 9338
 9339
 9340% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2799
 9341% [agent1,agent2,product,time]
 9342% Initiates(Deliver(agent1,agent2,product),
 9343%           Delivered(agent1,agent2,product),
 9344%           time).
 9345% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2802
 9346axiom(initiates(deliver(Agent1, Agent2, Product), delivered(Agent1, Agent2, Product), Time),
 9347    []).
 9348
 9349
 9350% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2804
 9351% [agent1,agent2,amount,time]
 9352% Initiates(SendEPO(agent1,agent2,amount),
 9353%           EPOSent(agent1,agent2,amount),
 9354%           time).
 9355% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2807
 9356axiom(initiates(sendEPO(Agent1, Agent2, Amount), ePOSent(Agent1, Agent2, Amount), Time),
 9357    []).
 9358
 9359
 9360% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2809
 9361% [agent1,agent2,product,amount,f1,f2,time]
 9362% agent1=% MusicStore &
 9363% agent2=Jen &
 9364% product=BritneyCD &
 9365% amount=1 &
 9366% f1=PurchaseRequestedJenMusicStoreBritneyCD1 &
 9367% f2=DeliveredMusicStoreJenBritneyCD ->
 9368% Initiates(SendQuote(agent1,agent2,product,amount),
 9369%           CC(agent1,agent2,f1,f2),
 9370%           time).
 9371% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2818
 9372axiom(initiates(sendQuote(Agent1, Agent2, Product, Amount), cc(Agent1, Agent2, F1, F2), Time),
 9373   
 9374    [ equals(Agent1, musicStore),
 9375      equals(Agent2, jen),
 9376      equals(Product, britneyCD),
 9377      equals(Amount, 1),
 9378      equals(F1, purchaseRequestedJenMusicStoreBritneyCD1),
 9379      equals(F2, deliveredMusicStoreJenBritneyCD)
 9380    ]).
 9381
 9382
 9383% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2820
 9384% [agent1,agent2,product,amount,f1,f2,time]
 9385% agent1=% Jen &
 9386% agent2=MusicStore &
 9387% product=BritneyCD &
 9388% amount=1 &
 9389% f1=DeliveredMusicStoreJenBritneyCD &
 9390% f2=EPOSentJenMusicStore1 &
 9391% !HoldsAt(Delivered(agent2,agent1,product),time) ->
 9392% Initiates(RequestPurchase(agent1,agent2,product,amount),
 9393%           CC(agent1,agent2,f1,f2),
 9394%           time).
 9395% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2830
 9396axiom(initiates(requestPurchase(Agent1, Agent2, Product, Amount), cc(Agent1, Agent2, F1, F2), Time),
 9397   
 9398    [ equals(Agent1, jen),
 9399      equals(Agent2, musicStore),
 9400      equals(Product, britneyCD),
 9401      equals(Amount, 1),
 9402      equals(F1, deliveredMusicStoreJenBritneyCD),
 9403      equals(F2, ePOSentJenMusicStore1),
 9404      not(holds_at(delivered(Agent2, Agent1, Product),
 9405                   Time))
 9406    ]).
 9407
 9408
 9409% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2832
 9410%; Delta
 9411
 9412% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2834
 9413% Delta: 
 9414next_axiom_uses(delta).
 9415 
 9416
 9417
 9418% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2834
 9419% [time]
 9420% HoldsAt(CC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time) &
 9421% HoldsAt(PurchaseRequested(Jen,MusicStore,BritneyCD,1),time) ->
 9422% Happens(CreateC(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time).
 9423% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2837
 9424axiom(happens(createC(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 9425   
 9426    [ holds_at(cc(musicStore,
 9427                  jen,
 9428                  purchaseRequestedJenMusicStoreBritneyCD1,
 9429                  deliveredMusicStoreJenBritneyCD),
 9430               Time),
 9431      holds_at(purchaseRequested(jen, musicStore, britneyCD, 1), Time)
 9432    ]).
 9433
 9434% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2839
 9435% Delta: 
 9436next_axiom_uses(delta).
 9437 
 9438
 9439
 9440% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2839
 9441% [time]
 9442% HoldsAt(CC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time) &
 9443% HoldsAt(PurchaseRequested(Jen, MusicStore, BritneyCD, 1),time) ->
 9444% Happens(DischargeCC(MusicStore,Jen,PurchaseRequestedJenMusicStoreBritneyCD1,DeliveredMusicStoreJenBritneyCD),time).
 9445% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2842
 9446axiom(happens(dischargeCC(musicStore, jen, purchaseRequestedJenMusicStoreBritneyCD1, deliveredMusicStoreJenBritneyCD), Time),
 9447   
 9448    [ holds_at(cc(musicStore,
 9449                  jen,
 9450                  purchaseRequestedJenMusicStoreBritneyCD1,
 9451                  deliveredMusicStoreJenBritneyCD),
 9452               Time),
 9453      holds_at(purchaseRequested(jen, musicStore, britneyCD, 1), Time)
 9454    ]).
 9455
 9456% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2844
 9457% Delta: 
 9458next_axiom_uses(delta).
 9459 
 9460
 9461
 9462% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2844
 9463% [time]
 9464% HoldsAt(CC(Jen, MusicStore, DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time) &
 9465% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 9466% Happens(CreateC(Jen,MusicStore,EPOSentJenMusicStore1),time).
 9467% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2847
 9468axiom(happens(createC(jen, musicStore, ePOSentJenMusicStore1), Time),
 9469   
 9470    [ holds_at(cc(jen,
 9471                  musicStore,
 9472                  deliveredMusicStoreJenBritneyCD,
 9473                  ePOSentJenMusicStore1),
 9474               Time),
 9475      holds_at(delivered(musicStore, jen, britneyCD), Time)
 9476    ]).
 9477
 9478% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2849
 9479% Delta: 
 9480next_axiom_uses(delta).
 9481 
 9482
 9483
 9484% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2849
 9485% [time]
 9486% HoldsAt(CC(Jen, MusicStore, DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time) &
 9487% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 9488% Happens(DischargeCC(Jen,MusicStore,DeliveredMusicStoreJenBritneyCD, EPOSentJenMusicStore1),time).
 9489% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2852
 9490axiom(happens(dischargeCC(jen, musicStore, deliveredMusicStoreJenBritneyCD, ePOSentJenMusicStore1), Time),
 9491   
 9492    [ holds_at(cc(jen,
 9493                  musicStore,
 9494                  deliveredMusicStoreJenBritneyCD,
 9495                  ePOSentJenMusicStore1),
 9496               Time),
 9497      holds_at(delivered(musicStore, jen, britneyCD), Time)
 9498    ]).
 9499
 9500% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2854
 9501% Delta: 
 9502next_axiom_uses(delta).
 9503 
 9504
 9505
 9506% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2854
 9507% [time]
 9508% HoldsAt(C(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time) &
 9509% HoldsAt(Delivered(MusicStore,Jen,BritneyCD),time) ->
 9510% Happens(DischargeC(MusicStore,Jen,DeliveredMusicStoreJenBritneyCD),time).
 9511% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2857
 9512axiom(happens(dischargeC(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 9513   
 9514    [ holds_at(c(musicStore, jen, deliveredMusicStoreJenBritneyCD), Time),
 9515      holds_at(delivered(musicStore, jen, britneyCD), Time)
 9516    ]).
 9517
 9518% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2859
 9519% Delta: 
 9520next_axiom_uses(delta).
 9521 
 9522
 9523
 9524% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2859
 9525% [time]
 9526% HoldsAt(C(Jen,MusicStore,EPOSentJenMusicStore1),time) &
 9527% HoldsAt(EPOSent(Jen,MusicStore,1),time) ->
 9528% Happens(DischargeC(Jen,MusicStore,EPOSentJenMusicStore1),time).
 9529% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2862
 9530axiom(happens(dischargeC(jen, musicStore, ePOSentJenMusicStore1), Time),
 9531   
 9532    [ holds_at(c(jen, musicStore, ePOSentJenMusicStore1), Time),
 9533      holds_at(ePOSent(jen, musicStore, 1), Time)
 9534    ]).
 9535
 9536% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2864
 9537% Delta: 
 9538next_axiom_uses(delta).
 9539 
 9540
 9541
 9542% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2864
 9543% Happens(RequestPurchase(Jen,MusicStore,BritneyCD,1),0).
 9544axiom(happens(requestPurchase(jen, musicStore, britneyCD, 1), t),
 9545    [is_time(0)]).
 9546
 9547% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2865
 9548% Delta: 
 9549next_axiom_uses(delta).
 9550 
 9551
 9552
 9553% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2865
 9554% Happens(Deliver(MusicStore,Jen,BritneyCD),2).
 9555axiom(happens(deliver(musicStore, jen, britneyCD), t2),
 9556    [is_time(2), b(t, t2), ignore(t+2=t2)]).
 9557
 9558% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2866
 9559% Delta: 
 9560next_axiom_uses(delta).
 9561 
 9562
 9563
 9564% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2866
 9565% Happens(SendEPO(Jen,MusicStore,1),4).
 9566axiom(happens(sendEPO(jen, musicStore, 1), t4),
 9567    [is_time(4), b(t, t4), ignore(t+4=t4)]).
 9568
 9569
 9570% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2868
 9571%; Gamma
 9572% [agent1,agent2,product,amount]
 9573% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2871
 9574% !HoldsAt(QuoteSent(agent1,agent2,product,amount),0).
 9575
 9576 /*  not(initially(quoteSent(Agent1,
 9577   			Agent2,
 9578   			Product,
 9579   			Amount))).
 9580 */
 9581axiom(not(initially(quoteSent(QuoteSent_Param, _, _, QuoteSent_Ret))),
 9582    []).
 9583
 9584
 9585% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2873
 9586% [agent1,agent2,product,amount]
 9587% !HoldsAt(PurchaseRequested(agent1,agent2,product,amount),0).
 9588
 9589 /*  not(initially(purchaseRequested(Agent1,
 9590   				Agent2,
 9591   				Product,
 9592   				Amount))).
 9593 */
 9594% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2874
 9595axiom(not(initially(purchaseRequested(PurchaseRequested_Param, _, _, PurchaseRequested_Ret))),
 9596    []).
 9597
 9598
 9599% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2876
 9600% [agent1,agent2,product]
 9601% !HoldsAt(Delivered(agent1,agent2,product),0).
 9602 %  not(initially(delivered(Agent1,Agent2,Product))).
 9603% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2877
 9604axiom(not(initially(delivered(Delivered_Param, _, Delivered_Ret))),
 9605    []).
 9606
 9607
 9608% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2879
 9609% [agent1,agent2,f]
 9610% !HoldsAt(C(agent1,agent2,f),0).
 9611 %  not(initially(c(Agent1,Agent2,F))).
 9612% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2880
 9613axiom(not(initially(c(C_Param, _, C_Ret))),
 9614    []).
 9615
 9616
 9617% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2882
 9618% [agent1,agent2,f1,f2]
 9619% !HoldsAt(CC(agent1,agent2,f1,f2),0).
 9620 %  not(initially(cc(Agent1,Agent2,F1,F2))).
 9621% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2883
 9622axiom(not(initially(cc(Cc_Param, _, _, Cc_Ret))),
 9623    []).
 9624
 9625
 9626% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2885
 9627% [agent1,agent2,amount]
 9628% !HoldsAt(EPOSent(agent1,agent2,amount),0).
 9629 %  not(initially(ePOSent(Agent1,Agent2,Amount))).
 9630% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2886
 9631axiom(not(initially(ePOSent(EPOSent_Param, _, EPOSent_Ret))),
 9632    []).
 9633
 9634% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2888
 9635% completion Delta Happens
 9636% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2889
 9637==> completion(delta).
 9638==> completion(happens).
 9639
 9640% range time 0 6
 9641% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2891
 9642==> range(time,0,6).
 9643
 9644% range offset 1 1
 9645% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2892
 9646==> range(offset,1,1).
 9647
 9648% range amount 1 1
 9649% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2893
 9650==> range(amount,1,1).
 9651%; End of file.
 9652%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 9653%; FILE: examples/Mueller2006/Chapter14/Vision.e
 9654%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
 9655%;
 9656%; Copyright (c) 2005 IBM Corporation and others.
 9657%; All rights reserved. This program and the accompanying materials
 9658%; are made available under the terms of the Common Public License v1.0
 9659%; which accompanies this distribution, and is available at
 9660%; http://www.eclipse.org/legal/cpl-v10.html
 9661%;
 9662%; Contributors:
 9663%; IBM - Initial implementation
 9664%;
 9665%; @inproceedings{ShanahanRandell:2004,
 9666%;   author = "Murray Shanahan and David A. Randell",
 9667%;   year = "2004",
 9668%;   title = "A logic-based formulation of active visual perception",
 9669%;   editor = "Didier Dubois and Christopher A. Welty and Mary-Anne Williams",
 9670%;   booktitle = "\uppercase{P}roceedings of the \uppercase{N}inth \uppercase{I}nternational \uppercase{C}onference on \uppercase{P}rinciples of \uppercase{K}nowledge \uppercase{R}epresentation and \uppercase{R}easoning",
 9671%;   pages = "64--72",
 9672%;   address = "Menlo Park, CA",
 9673%;   publisher = "AAAI Press",
 9674%; }
 9675%;
 9676%; @book{Mueller:2006,
 9677%;   author = "Erik T. Mueller",
 9678%;   year = "2006",
 9679%;   title = "Commonsense Reasoning",
 9680%;   address = "San Francisco",
 9681%;   publisher = "Morgan Kaufmann/Elsevier",
 9682%; }
 9683%;
 9684
 9685% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2931
 9686% option modeldiff on
 9687% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2932
 9688:- set_ec_option(modeldiff, on). 9689
 9690% load foundations/Root.e
 9691
 9692% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2934
 9693% load foundations/EC.e
 9694
 9695% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2936
 9696% sort object
 9697% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2937
 9698==> sort(object).
 9699
 9700% sort shape
 9701% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2938
 9702==> sort(shape).
 9703
 9704% sort aspect
 9705% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2939
 9706==> sort(aspect).
 9707
 9708% object Object1
 9709% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2941
 9710==> t(object,object1).
 9711
 9712% aspect Aspect1, Aspect2, Aspect3
 9713% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2942
 9714==> t(aspect,aspect1).
 9715==> t(aspect,aspect2).
 9716==> t(aspect,aspect3).
 9717
 9718% shape Shape1, Shape2
 9719% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2943
 9720==> t(shape,shape1).
 9721==> t(shape,shape2).
 9722
 9723% predicate Shape(object,shape)
 9724 %  predicate(shape(object,shape)).
 9725% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2945
 9726==> mpred_prop(shape(object,shape),predicate).
 9727==> meta_argtypes(shape(object,shape)).
 9728
 9729% predicate Arc(shape,aspect,aspect)
 9730 %  predicate(arc(shape,aspect,aspect)).
 9731% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2946
 9732==> mpred_prop(arc(shape,aspect,aspect),predicate).
 9733==> meta_argtypes(arc(shape,aspect,aspect)).
 9734
 9735% fluent Aspect(object,aspect)
 9736 %  fluent(aspect(object,aspect)).
 9737% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2947
 9738==> mpred_prop(aspect(object,aspect),fluent).
 9739==> meta_argtypes(aspect(object,aspect)).
 9740
 9741% event Change(object,aspect,aspect)
 9742 %  event(change(object,aspect,aspect)).
 9743% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2948
 9744==> mpred_prop(change(object,aspect,aspect),event).
 9745==> meta_argtypes(change(object,aspect,aspect)).
 9746
 9747
 9748% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2949
 9749%; Sigma
 9750% [object,aspect1,aspect2,shape,time]
 9751% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2952
 9752% HoldsAt(Aspect(object,aspect1),time) &
 9753% Shape(object,shape) &
 9754% (Arc(shape,aspect1,aspect2) |
 9755%  Arc(shape,aspect2,aspect1)) ->
 9756% Initiates(Change(object,aspect1,aspect2),Aspect(object,aspect2),time).
 9757% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2956
 9758axiom(initiates(change(Object, Aspect1, Aspect2), aspect(Object, Aspect2), Time),
 9759   
 9760    [ arc(Shape, Aspect1, Aspect2),
 9761      holds_at(aspect(Object, Aspect1), Time),
 9762      shape(Object, Shape)
 9763    ]).
 9764axiom(initiates(change(Object, Aspect1, Aspect2), aspect(Object, Aspect2), Time),
 9765   
 9766    [ arc(Shape, Aspect2, Aspect1),
 9767      holds_at(aspect(Object, Aspect1), Time),
 9768      shape(Object, Shape)
 9769    ]).
 9770
 9771
 9772% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2958
 9773% [object,aspect1,aspect2,shape,time]
 9774% HoldsAt(Aspect(object,aspect1),time) &
 9775% Shape(object,shape) &
 9776% (Arc(shape,aspect1,aspect2) |
 9777%  Arc(shape,aspect2,aspect1)) ->
 9778% Terminates(Change(object,aspect1,aspect2),Aspect(object,aspect1),time).
 9779% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2963
 9780axiom(terminates(change(Object, Aspect1, Aspect2), aspect(Object, Aspect1), Time),
 9781   
 9782    [ arc(Shape, Aspect1, Aspect2),
 9783      holds_at(aspect(Object, Aspect1), Time),
 9784      shape(Object, Shape)
 9785    ]).
 9786axiom(terminates(change(Object, Aspect1, Aspect2), aspect(Object, Aspect1), Time),
 9787   
 9788    [ arc(Shape, Aspect2, Aspect1),
 9789      holds_at(aspect(Object, Aspect1), Time),
 9790      shape(Object, Shape)
 9791    ]).
 9792
 9793
 9794% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2965
 9795%; preconditions (added)
 9796% [object,aspect1,aspect2,time]
 9797% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2968
 9798% Happens(Change(object,aspect1,aspect2),time) ->
 9799% HoldsAt(Aspect(object,aspect1),time).
 9800% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2969
 9801axiom(requires(change(Object, Aspect1, Aspect2), Time),
 9802    [holds_at(aspect(Object, Aspect1), Time)]).
 9803
 9804
 9805% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2971
 9806% [object,aspect1,aspect2,aspect3,time]
 9807% Happens(Change(object,aspect1,aspect2),time) &
 9808% Happens(Change(object,aspect1,aspect3),time) ->
 9809% aspect2=aspect3.
 9810% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2974
 9811axiom(Aspect2=Aspect3,
 9812   
 9813    [ happens(change(Object, Aspect1, Aspect2), Time),
 9814      happens(change(Object, Aspect1, Aspect3), Time)
 9815    ]).
 9816
 9817
 9818% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2976
 9819%; Psi
 9820% [object,shape1,shape2]
 9821% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2979
 9822% Shape(object,shape1) &
 9823% Shape(object,shape2) ->
 9824% shape1=shape2.
 9825% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2981
 9826axiom(Shape1=Shape2,
 9827    [shape(Object, Shape1), shape(Object, Shape2)]).
 9828
 9829
 9830% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2983
 9831% [object,aspect1,aspect2,time]
 9832% HoldsAt(Aspect(object,aspect1),time) &
 9833% HoldsAt(Aspect(object,aspect2),time) ->
 9834% aspect1=aspect2.
 9835% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2986
 9836axiom(Aspect1=Aspect2,
 9837   
 9838    [ holds_at(aspect(Object, Aspect1), Time),
 9839      holds_at(aspect(Object, Aspect2), Time)
 9840    ]).
 9841
 9842
 9843% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2988
 9844% [aspect1,aspect2]
 9845% Arc(Shape1,aspect1,aspect2) <->
 9846% (aspect1=Aspect1 & aspect2=Aspect2).
 9847
 9848 /*  arc(shape1, Aspect1, Aspect2) <->
 9849       Aspect1=aspect1,
 9850       Aspect2=aspect2.
 9851 */
 9852% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2990
 9853axiom(arc(shape1, Aspect1, Aspect2),
 9854    [equals(Aspect1, aspect1), equals(Aspect2, aspect2)]).
 9855
 9856 /*   if(arc(shape1, Aspect1, Aspect2),
 9857          (Aspect1=aspect1, Aspect2=aspect2)).
 9858 */
 9859
 9860 /*  not(arc(shape1, Equals_Param, Equals_Param3)) :-
 9861       (   not(equals(Equals_Param, aspect1))
 9862       ;   not(equals(Equals_Param3, aspect2))
 9863       ).
 9864 */
 9865axiom(not(arc(shape1, Equals_Param, Equals_Param3)),
 9866    [not(equals(Equals_Param, aspect1))]).
 9867axiom(not(arc(shape1, Equals_Param, Equals_Param3)),
 9868    [not(equals(Equals_Param3, aspect2))]).
 9869
 9870 /*  equals(Equals_Param4, aspect1) :-
 9871       arc(shape1, Equals_Param4, Arc_Ret).
 9872 */
 9873axiom(equals(Equals_Param4, aspect1),
 9874    [arc(shape1, Equals_Param4, Arc_Ret)]).
 9875
 9876 /*  equals(Equals_Param6, aspect2) :-
 9877       arc(shape1, _, Equals_Param6).
 9878 */
 9879axiom(equals(Equals_Param6, aspect2),
 9880    [arc(shape1, _, Equals_Param6)]).
 9881
 9882
 9883% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2992
 9884% [aspect1,aspect2]
 9885% Arc(Shape2,aspect1,aspect2) <->
 9886% ((aspect1=Aspect1 & aspect2=Aspect3) |
 9887%  (aspect1=Aspect3 & aspect2=Aspect2)).
 9888
 9889 /*  arc(shape2, Aspect1, Aspect2) <->
 9890       (   Aspect1=aspect1,
 9891           Aspect2=aspect3
 9892       ;   Aspect1=aspect3,
 9893           Aspect2=aspect2
 9894       ).
 9895 */
 9896% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2995
 9897axiom(arc(shape2, Aspect1, Aspect2),
 9898    [equals(Aspect1, aspect1), equals(Aspect2, aspect3)]).
 9899axiom(arc(shape2, Aspect1, Aspect2),
 9900    [equals(Aspect1, aspect3), equals(Aspect2, aspect2)]).
 9901
 9902 /*   if(arc(shape2, Aspect1, Aspect2),
 9903          (Aspect1=aspect1, Aspect2=aspect3;Aspect1=aspect3, Aspect2=aspect2)).
 9904 */
 9905
 9906 /*  not(arc(shape2, Equals_Param, Equals_Param3)) :-
 9907       (   not(equals(Equals_Param, aspect1))
 9908       ;   not(equals(Equals_Param3, aspect3))
 9909       ),
 9910       (   not(equals(Equals_Param, aspect3))
 9911       ;   not(equals(Equals_Param3, aspect2))
 9912       ).
 9913 */
 9914axiom(not(arc(shape2, Equals_Param, Equals_Param3)),
 9915   
 9916    [ not(equals(Equals_Param, aspect3)),
 9917      not(equals(Equals_Param, aspect1))
 9918    ]).
 9919axiom(not(arc(shape2, Equals_Param, Equals_Param3)),
 9920   
 9921    [ not(equals(Equals_Param3, aspect2)),
 9922      not(equals(Equals_Param, aspect1))
 9923    ]).
 9924axiom(not(arc(shape2, Equals_Param, Equals_Param3)),
 9925   
 9926    [ not(equals(Equals_Param, aspect3)),
 9927      not(equals(Equals_Param3, aspect3))
 9928    ]).
 9929axiom(not(arc(shape2, Equals_Param, Equals_Param3)),
 9930   
 9931    [ not(equals(Equals_Param3, aspect2)),
 9932      not(equals(Equals_Param3, aspect3))
 9933    ]).
 9934
 9935 /*  equals(Equals_Param4, aspect1) :-
 9936       (   not(equals(Equals_Param4, aspect3))
 9937       ;   not(equals(Equals_Param5, aspect2))
 9938       ),
 9939       arc(shape2, Equals_Param4, Equals_Param5).
 9940 */
 9941axiom(equals(Equals_Param4, aspect1),
 9942   
 9943    [ not(equals(Equals_Param4, aspect3)),
 9944      arc(shape2, Equals_Param4, Equals_Param5)
 9945    ]).
 9946axiom(equals(Equals_Param4, aspect1),
 9947   
 9948    [ not(equals(Equals_Param5, aspect2)),
 9949      arc(shape2, Equals_Param4, Equals_Param5)
 9950    ]).
 9951
 9952 /*  equals(Equals_Param6, aspect3) :-
 9953       (   not(equals(Equals_Param7, aspect3))
 9954       ;   not(equals(Equals_Param6, aspect2))
 9955       ),
 9956       arc(shape2, Equals_Param7, Equals_Param6).
 9957 */
 9958axiom(equals(Equals_Param6, aspect3),
 9959   
 9960    [ not(equals(Equals_Param7, aspect3)),
 9961      arc(shape2, Equals_Param7, Equals_Param6)
 9962    ]).
 9963axiom(equals(Equals_Param6, aspect3),
 9964   
 9965    [ not(equals(Equals_Param6, aspect2)),
 9966      arc(shape2, Equals_Param7, Equals_Param6)
 9967    ]).
 9968
 9969 /*  equals(Equals_Param8, aspect3) :-
 9970       (   not(equals(Equals_Param8, aspect1))
 9971       ;   not(equals(Equals_Param9, aspect3))
 9972       ),
 9973       arc(shape2, Equals_Param8, Equals_Param9).
 9974 */
 9975axiom(equals(Equals_Param8, aspect3),
 9976   
 9977    [ not(equals(Equals_Param8, aspect1)),
 9978      arc(shape2, Equals_Param8, Equals_Param9)
 9979    ]).
 9980axiom(equals(Equals_Param8, aspect3),
 9981   
 9982    [ not(equals(Equals_Param9, aspect3)),
 9983      arc(shape2, Equals_Param8, Equals_Param9)
 9984    ]).
 9985
 9986 /*  equals(Equals_Param10, aspect2) :-
 9987       (   not(equals(Equals_Param11, aspect1))
 9988       ;   not(equals(Equals_Param10, aspect3))
 9989       ),
 9990       arc(shape2, Equals_Param11, Equals_Param10).
 9991 */
 9992axiom(equals(Equals_Param10, aspect2),
 9993   
 9994    [ not(equals(Equals_Param11, aspect1)),
 9995      arc(shape2, Equals_Param11, Equals_Param10)
 9996    ]).
 9997axiom(equals(Equals_Param10, aspect2),
 9998   
 9999    [ not(equals(Equals_Param10, aspect3)),
10000      arc(shape2, Equals_Param11, Equals_Param10)
10001    ]).
10002
10003
10004% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2997
10005%; Gamma
10006
10007
10008% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:2999
10009% HoldsAt(Aspect(Object1,Aspect1),0).
10010axiom(initially(aspect(object1, aspect1)),
10011    []).
10012
10013
10014% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3000
10015% HoldsAt(Aspect(Object1,Aspect2),1).
10016holds_at(aspect(object1,aspect2),1).
10017
10018
10019% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3002
10020%;completion Delta Happens
10021
10022% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3004
10023% range time 0 1
10024% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3005
10025==> range(time,0,1).
10026
10027% range offset 1 1
10028% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3006
10029==> range(offset,1,1).
10030%; End of file.
10031%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10032%; FILE: examples/Mueller2006/Chapter14/Workflow.e
10033%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10034%;
10035%; Copyright (c) 2005 IBM Corporation and others.
10036%; All rights reserved. This program and the accompanying materials
10037%; are made available under the terms of the Common Public License v1.0
10038%; which accompanies this distribution, and is available at
10039%; http://www.eclipse.org/legal/cpl-v10.html
10040%;
10041%; Contributors:
10042%; IBM - Initial implementation
10043%;
10044%; @incollection{CicekliYildirim:2000,
10045%;   author = "Nihan Kesim Cicekli and Yakup Yildirim",
10046%;   year = "2000",
10047%;   title = "Formalizing workflows using the event calculus",
10048%;   editor = "Mohamed T. Ibrahim and Josef K{\"{u}}ng and Norman Revell",
10049%;   booktitle = "Database and Expert Systems Applications",
10050%;   series = "Lecture Notes in Computer Science",
10051%;   volume = "1873",
10052%;   pages = "222--231",
10053%;   address = "Berlin",
10054%;   publisher = "Springer",
10055%; }
10056%;
10057%; @unpublished{WFMC:1999,
10058%;   author = "{Workflow Management Coalition}",
10059%;   year = "1999",
10060%;   title = "\uppercase{W}orkflow \uppercase{M}anagement \uppercase{C}oalition Terminology \& Glossary",
10061%;   howpublished = "Document Number WFMC-TC-1011, Document Status -- Issue 3.0, Workflow Management Coalition, Winchester, UK",
10062%; }
10063%;
10064%; @book{Mueller:2006,
10065%;   author = "Erik T. Mueller",
10066%;   year = "2006",
10067%;   title = "Commonsense Reasoning",
10068%;   address = "San Francisco",
10069%;   publisher = "Morgan Kaufmann/Elsevier",
10070%; }
10071%;
10072
10073% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3053
10074% option modeldiff on
10075% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3054
10076:- set_ec_option(modeldiff, on).10077
10078% load foundations/Root.e
10079
10080% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3056
10081% load foundations/EC.e
10082
10083% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3058
10084% sort activity
10085% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3059
10086==> sort(activity).
10087
10088% sort condition
10089% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3060
10090==> sort(condition).
10091
10092% activity A, B, C1, C2, C3, D, E1, E2, E3, F, G
10093% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3061
10094==> t(activity,a).
10095==> t(activity,b).
10096==> t(activity,c1).
10097==> t(activity,c2).
10098==> t(activity,c3).
10099==> t(activity,d).
10100==> t(activity,e1).
10101==> t(activity,e2).
10102==> t(activity,e3).
10103==> t(activity,f).
10104==> t(activity,g).
10105
10106% condition E1C, E2C, E3C, FC
10107% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3062
10108==> t(condition,e1c).
10109==> t(condition,e2c).
10110==> t(condition,e3c).
10111==> t(condition,fc).
10112
10113% fluent Active(activity)
10114 %  fluent(active(activity)).
10115% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3064
10116==> mpred_prop(active(activity),fluent).
10117==> meta_argtypes(active(activity)).
10118
10119% fluent Completed(activity)
10120 %  fluent(completed(activity)).
10121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3065
10122==> mpred_prop(completed(activity),fluent).
10123==> meta_argtypes(completed(activity)).
10124
10125% fluent Condition(condition)
10126 %  fluent(condition(condition)).
10127% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3066
10128==> mpred_prop(condition(condition),fluent).
10129==> meta_argtypes(condition(condition)).
10130
10131% noninertial Condition
10132% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3067
10133==> noninertial(condition).
10134
10135% event Start(activity)
10136 %  event(start(activity)).
10137% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3069
10138==> mpred_prop(start(activity),event).
10139==> meta_argtypes(start(activity)).
10140
10141% event End(activity)
10142 %  event(end(activity)).
10143% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3070
10144==> mpred_prop(end(activity),event).
10145==> meta_argtypes(end(activity)).
10146
10147
10148% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3071
10149%; Sigma
10150% [activity,time]
10151% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3074
10152% Initiates(Start(activity),Active(activity),time).
10153axiom(initiates(start(Activity), active(Activity), Time),
10154    []).
10155
10156
10157% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3076
10158% [activity,time]
10159% Terminates(Start(activity),Completed(activity),time).
10160% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3077
10161axiom(terminates(start(Activity), completed(Activity), Time),
10162    []).
10163
10164
10165% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3079
10166% [activity,time]
10167% Initiates(End(activity),Completed(activity),time).
10168% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3080
10169axiom(initiates(end(Activity), completed(Activity), Time),
10170    []).
10171
10172
10173% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3082
10174% [activity,time]
10175% Terminates(End(activity),Active(activity),time).
10176% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3083
10177axiom(terminates(end(Activity), active(Activity), Time),
10178    []).
10179
10180
10181% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3085
10182%; Delta
10183%; A; B
10184
10185% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3088
10186% Delta: 
10187next_axiom_uses(delta).
10188 
10189
10190
10191% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3088
10192% [time]
10193% !HoldsAt(Active(B),time) &
10194% !HoldsAt(Completed(A),time-1) &
10195% HoldsAt(Completed(A),time) ->
10196% Happens(Start(B),time).
10197% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3092
10198axiom(happens(start(b), start),
10199   
10200    [ not(holds_at(active(b), start)),
10201      not(holds_at(completed(a), t)),
10202      holds_at(completed(a), start),
10203      b(t, start),
10204      ignore(start-1=t)
10205    ]).
10206
10207
10208% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3094
10209%; B; AND-split C1, C2, C3
10210
10211% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3095
10212% Delta: 
10213next_axiom_uses(delta).
10214 
10215
10216
10217% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3095
10218% [time]
10219% !HoldsAt(Active(C1),time) &
10220% !HoldsAt(Completed(B),time-1) &
10221% HoldsAt(Completed(B),time) ->
10222% Happens(Start(C1),time).
10223% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3099
10224axiom(happens(start(c1), start),
10225   
10226    [ not(holds_at(active(c1), start)),
10227      not(holds_at(completed(b), t)),
10228      holds_at(completed(b), start),
10229      b(t, start),
10230      ignore(start-1=t)
10231    ]).
10232
10233% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3101
10234% Delta: 
10235next_axiom_uses(delta).
10236 
10237
10238
10239% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3101
10240% [time]
10241% !HoldsAt(Active(C2),time) &
10242% !HoldsAt(Completed(B),time-1) &
10243% HoldsAt(Completed(B),time) ->
10244% Happens(Start(C2),time).
10245% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3105
10246axiom(happens(start(c2), start),
10247   
10248    [ not(holds_at(active(c2), start)),
10249      not(holds_at(completed(b), t)),
10250      holds_at(completed(b), start),
10251      b(t, start),
10252      ignore(start-1=t)
10253    ]).
10254
10255% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3107
10256% Delta: 
10257next_axiom_uses(delta).
10258 
10259
10260
10261% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3107
10262% [time]
10263% !HoldsAt(Active(C3),time) &
10264% !HoldsAt(Completed(B),time-1) &
10265% HoldsAt(Completed(B),time) ->
10266% Happens(Start(C3),time).
10267% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3111
10268axiom(happens(start(c3), start),
10269   
10270    [ not(holds_at(active(c3), start)),
10271      not(holds_at(completed(b), t)),
10272      holds_at(completed(b), start),
10273      b(t, start),
10274      ignore(start-1=t)
10275    ]).
10276
10277
10278% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3113
10279%; AND-join C1, C2, C3; D
10280
10281% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3114
10282% Delta: 
10283next_axiom_uses(delta).
10284 
10285
10286
10287% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3114
10288% [time]
10289% !HoldsAt(Active(D),time) &
10290% ((!HoldsAt(Completed(C1),time-1) & HoldsAt(Completed(C1),time))|
10291%  (!HoldsAt(Completed(C2),time-1) & HoldsAt(Completed(C2),time))|
10292%  (!HoldsAt(Completed(C3),time-1) & HoldsAt(Completed(C3),time))) &
10293% HoldsAt(Completed(C1),time) &
10294% HoldsAt(Completed(C2),time) &
10295% HoldsAt(Completed(C3),time) ->
10296% Happens(Start(D),time).
10297% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3122
10298axiom(happens(start(d), start),
10299   
10300    [ not(holds_at(completed(c1), t)),
10301      holds_at(completed(c1), start),
10302      not(holds_at(active(d), start)),
10303      holds_at(completed(c1), start),
10304      holds_at(completed(c2), start),
10305      holds_at(completed(c3), start),
10306      b(t, start),
10307      ignore(start-1=t)
10308    ]).
10309axiom(happens(start(d), start),
10310   
10311    [ not(holds_at(completed(c2), t)),
10312      holds_at(completed(c2), start),
10313      not(holds_at(active(d), start)),
10314      holds_at(completed(c1), start),
10315      holds_at(completed(c2), start),
10316      holds_at(completed(c3), start),
10317      b(t, start),
10318      ignore(start-1=t)
10319    ]).
10320axiom(happens(start(d), start),
10321   
10322    [ not(holds_at(completed(c3), t)),
10323      holds_at(completed(c3), start),
10324      not(holds_at(active(d), start)),
10325      holds_at(completed(c1), start),
10326      holds_at(completed(c2), start),
10327      holds_at(completed(c3), start),
10328      b(t, start),
10329      ignore(start-1=t)
10330    ]).
10331
10332
10333% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3124
10334%; D; XOR-split E1, E2, E3
10335
10336% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3125
10337% Delta: 
10338next_axiom_uses(delta).
10339 
10340
10341
10342% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3125
10343% [time]
10344% !HoldsAt(Active(E1),time) &
10345% !HoldsAt(Completed(D),time-1) &
10346% HoldsAt(Completed(D),time) &
10347% HoldsAt(Condition(E1C),time) ->
10348% Happens(Start(E1),time).
10349% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3130
10350axiom(happens(start(e1), start),
10351   
10352    [ not(holds_at(active(e1), start)),
10353      not(holds_at(completed(d), t)),
10354      holds_at(completed(d), start),
10355      holds_at(condition(e1c), start),
10356      b(t, start),
10357      ignore(start-1=t)
10358    ]).
10359
10360% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3132
10361% Delta: 
10362next_axiom_uses(delta).
10363 
10364
10365
10366% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3132
10367% [time]
10368% !HoldsAt(Active(E2),time) &
10369% !HoldsAt(Completed(D),time-1) &
10370% HoldsAt(Completed(D),time) &
10371% HoldsAt(Condition(E2C),time) ->
10372% Happens(Start(E2),time).
10373% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3137
10374axiom(happens(start(e2), start),
10375   
10376    [ not(holds_at(active(e2), start)),
10377      not(holds_at(completed(d), t)),
10378      holds_at(completed(d), start),
10379      holds_at(condition(e2c), start),
10380      b(t, start),
10381      ignore(start-1=t)
10382    ]).
10383
10384% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3139
10385% Delta: 
10386next_axiom_uses(delta).
10387 
10388
10389
10390% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3139
10391% [time]
10392% !HoldsAt(Active(E3),time) &
10393% !HoldsAt(Completed(D),time-1) &
10394% HoldsAt(Completed(D),time) &
10395% HoldsAt(Condition(E3C),time) ->
10396% Happens(Start(E3),time).
10397% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3144
10398axiom(happens(start(e3), start),
10399   
10400    [ not(holds_at(active(e3), start)),
10401      not(holds_at(completed(d), t)),
10402      holds_at(completed(d), start),
10403      holds_at(condition(e3c), start),
10404      b(t, start),
10405      ignore(start-1=t)
10406    ]).
10407
10408
10409% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3146
10410%; XOR-join E1, E2, E3; F
10411
10412% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3147
10413% Delta: 
10414next_axiom_uses(delta).
10415 
10416
10417
10418% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3147
10419% [time]
10420% !HoldsAt(Active(F),time) &
10421% ((!HoldsAt(Completed(E1),time-1) & HoldsAt(Completed(E1),time))|
10422%  (!HoldsAt(Completed(E2),time-1) & HoldsAt(Completed(E2),time))|
10423%  (!HoldsAt(Completed(E3),time-1) & HoldsAt(Completed(E3),time))) ->
10424% Happens(Start(F),time).
10425% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3152
10426axiom(happens(start(f), start),
10427   
10428    [ not(holds_at(completed(e1), t)),
10429      holds_at(completed(e1), start),
10430      not(holds_at(active(f), start)),
10431      b(t, start),
10432      ignore(start-1=t)
10433    ]).
10434axiom(happens(start(f), start),
10435   
10436    [ not(holds_at(completed(e2), t)),
10437      holds_at(completed(e2), start),
10438      not(holds_at(active(f), start)),
10439      b(t, start),
10440      ignore(start-1=t)
10441    ]).
10442axiom(happens(start(f), start),
10443   
10444    [ not(holds_at(completed(e3), t)),
10445      holds_at(completed(e3), start),
10446      not(holds_at(active(f), start)),
10447      b(t, start),
10448      ignore(start-1=t)
10449    ]).
10450
10451
10452% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3154
10453%; while (FC) F; G
10454
10455% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3155
10456% Delta: 
10457next_axiom_uses(delta).
10458 
10459
10460
10461% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3155
10462% [time]
10463% !HoldsAt(Active(F),time) &
10464% !HoldsAt(Completed(F),time-1) &
10465% HoldsAt(Completed(F),time) &
10466% HoldsAt(Condition(FC),time) ->
10467% Happens(Start(F),time).
10468% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3160
10469axiom(happens(start(f), start),
10470   
10471    [ not(holds_at(active(f), start)),
10472      not(holds_at(completed(f), t)),
10473      holds_at(completed(f), start),
10474      holds_at(condition(fc), start),
10475      b(t, start),
10476      ignore(start-1=t)
10477    ]).
10478
10479% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3162
10480% Delta: 
10481next_axiom_uses(delta).
10482 
10483
10484
10485% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3162
10486% [time]
10487% !HoldsAt(Active(G),time) &
10488% !HoldsAt(Completed(F),time-1) &
10489% HoldsAt(Completed(F),time) &
10490% !HoldsAt(Condition(FC),time) ->
10491% Happens(Start(G),time).
10492% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3167
10493axiom(happens(start(g), start),
10494   
10495    [ not(holds_at(active(g), start)),
10496      not(holds_at(completed(f), t)),
10497      holds_at(completed(f), start),
10498      not(holds_at(condition(fc), start)),
10499      b(t, start),
10500      ignore(start-1=t)
10501    ]).
10502
10503% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3169
10504% Delta: 
10505next_axiom_uses(delta).
10506 
10507
10508
10509% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3169
10510% Happens(Start(A),0).
10511axiom(happens(start(a), t),
10512    [is_time(0)]).
10513
10514% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3170
10515% Delta: 
10516next_axiom_uses(delta).
10517 
10518
10519
10520% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3170
10521% Happens(End(A),1).
10522axiom(happens(end(a), start),
10523    [is_time(1), b(t, start), ignore(t+1=start)]).
10524
10525% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3171
10526% Delta: 
10527next_axiom_uses(delta).
10528 
10529
10530
10531% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3171
10532% Happens(End(B),3).
10533axiom(happens(end(b), t3),
10534    [is_time(3), b(t, t3), ignore(t+3=t3)]).
10535
10536% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3172
10537% Delta: 
10538next_axiom_uses(delta).
10539 
10540
10541
10542% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3172
10543% Happens(End(C1),5).
10544axiom(happens(end(c1), t5),
10545    [is_time(5), b(t, t5), ignore(t+5=t5)]).
10546
10547% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3173
10548% Delta: 
10549next_axiom_uses(delta).
10550 
10551
10552
10553% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3173
10554% Happens(End(C2),6).
10555axiom(happens(end(c2), t6),
10556    [is_time(6), b(t, t6), ignore(t+6=t6)]).
10557
10558% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3174
10559% Delta: 
10560next_axiom_uses(delta).
10561 
10562
10563
10564% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3174
10565% Happens(End(C3),7).
10566axiom(happens(end(c3), t7),
10567    [is_time(7), b(t, t7), ignore(t+7=t7)]).
10568
10569% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3175
10570% Delta: 
10571next_axiom_uses(delta).
10572 
10573
10574
10575% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3175
10576% Happens(End(D),9).
10577axiom(happens(end(d), t9),
10578    [is_time(9), b(t, t9), ignore(t+9=t9)]).
10579
10580% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3176
10581% Delta: 
10582next_axiom_uses(delta).
10583 
10584
10585
10586% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3176
10587% Happens(End(E2),11).
10588axiom(happens(end(e2), t11),
10589    [is_time(11), b(t, t11), ignore(t+11=t11)]).
10590
10591% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3177
10592% Delta: 
10593next_axiom_uses(delta).
10594 
10595
10596
10597% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3177
10598% Happens(End(F),13).
10599axiom(happens(end(f), t13),
10600    [is_time(13), b(t, t13), ignore(t+13=t13)]).
10601
10602% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3178
10603% Delta: 
10604next_axiom_uses(delta).
10605 
10606
10607
10608% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3178
10609% Happens(End(F),15).
10610axiom(happens(end(f), t15),
10611    [is_time(15), b(t, t15), ignore(t+15=t15)]).
10612
10613
10614% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3180
10615%; Gamma
10616% [activity]
10617 % !HoldsAt(Active(activity),0).
10618 %  not(initially(active(Activity))).
10619% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3182
10620axiom(not(initially(active(Active_Ret))),
10621    []).
10622
10623
10624% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3183
10625% [activity]
10626 % !HoldsAt(Completed(activity),0).
10627 %  not(initially(completed(Activity))).
10628axiom(not(initially(completed(Completed_Ret))),
10629    []).
10630
10631
10632% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3184
10633% [time]
10634 % time=% 14 <-> HoldsAt(Condition(FC),time).
10635
10636 /*  Time=14 <->
10637       holds_at(condition(fc), Time).
10638 */
10639axiom(Time=14,
10640    [holds_at(condition(fc), Time)]).
10641axiom(holds_at(condition(fc), Time),
10642    [equals(Time, 14)]).
10643
10644
10645% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3185
10646% [time]
10647 % !HoldsAt(Condition(E1C),time).
10648 %  not(holds_at(condition(e1c),Time)).
10649axiom(not(holds_at(condition(e1c), Time1)),
10650    []).
10651
10652
10653% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3186
10654% [time]
10655 % time=% 10 <-> HoldsAt(Condition(E2C),time).
10656
10657 /*  Time=10 <->
10658       holds_at(condition(e2c), Time).
10659 */
10660axiom(Time=10,
10661    [holds_at(condition(e2c), Time)]).
10662axiom(holds_at(condition(e2c), Time),
10663    [equals(Time, 10)]).
10664
10665
10666% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3187
10667% [time]
10668 % !HoldsAt(Condition(E3C),time).
10669 %  not(holds_at(condition(e3c),Time)).
10670axiom(not(holds_at(condition(e3c), Time1)),
10671    []).
10672
10673% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3189
10674% completion Delta Happens
10675% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3190
10676==> completion(delta).
10677==> completion(happens).
10678
10679% range time 0 18
10680% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3192
10681==> range(time,0,18).
10682
10683% range offset 1 1
10684% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3193
10685==> range(offset,1,1).
10686%; End of file.
10687%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10688%; FILE: examples/Mueller2006/Chapter6/ThielscherCircuit1.e
10689%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10690%;
10691%; Copyright (c) 2005 IBM Corporation and others.
10692%; All rights reserved. This program and the accompanying materials
10693%; are made available under the terms of the Common Public License v1.0
10694%; which accompanies this distribution, and is available at
10695%; http://www.eclipse.org/legal/cpl-v10.html
10696%;
10697%; Contributors:
10698%; IBM - Initial implementation
10699%;
10700%; @article{Thielscher:1997,
10701%;   author = "Michael Thielscher",
10702%;   year = "1997",
10703%;   title = "Ramification and causality",
10704%;   journal = "Artificial Intelligence",
10705%;   volume = "89",
10706%;   pages = "317--364",
10707%; }
10708%;
10709%; @book{Mueller:2006,
10710%;   author = "Erik T. Mueller",
10711%;   year = "2006",
10712%;   title = "Commonsense Reasoning",
10713%;   address = "San Francisco",
10714%;   publisher = "Morgan Kaufmann/Elsevier",
10715%; }
10716%;
10717
10718% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3229
10719% load foundations/Root.e
10720
10721% load foundations/EC.e
10722
10723% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3231
10724% load foundations/ECCausal.e
10725
10726% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3233
10727% sort switch
10728% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3234
10729==> sort(switch).
10730
10731% sort relay
10732% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3235
10733==> sort(relay).
10734
10735% sort light
10736% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3236
10737==> sort(light).
10738
10739% switch S1, S2, S3
10740% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3238
10741==> t(switch,s1).
10742==> t(switch,s2).
10743==> t(switch,s3).
10744
10745% relay R
10746% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3239
10747==> t(relay,r).
10748
10749% light L
10750% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3240
10751==> t(light,l).
10752
10753% event Light(light)
10754 %  event(light(light)).
10755% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3242
10756==> mpred_prop(light(light),event).
10757==> meta_argtypes(light(light)).
10758
10759% event Close(switch)
10760 %  event(close(switch)).
10761% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3243
10762==> mpred_prop(close(switch),event).
10763==> meta_argtypes(close(switch)).
10764
10765% event Open(switch)
10766 %  event(open(switch)).
10767% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3244
10768==> mpred_prop(open(switch),event).
10769==> meta_argtypes(open(switch)).
10770
10771% event Activate(relay)
10772 %  event(activate(relay)).
10773% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3245
10774==> mpred_prop(activate(relay),event).
10775==> meta_argtypes(activate(relay)).
10776
10777% fluent Lit(light)
10778 %  fluent(lit(light)).
10779% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3247
10780==> mpred_prop(lit(light),fluent).
10781==> meta_argtypes(lit(light)).
10782
10783% fluent Closed(switch)
10784 %  fluent(closed(switch)).
10785% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3248
10786==> mpred_prop(closed(switch),fluent).
10787==> meta_argtypes(closed(switch)).
10788
10789% fluent Activated(relay)
10790 %  fluent(activated(relay)).
10791% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3249
10792==> mpred_prop(activated(relay),fluent).
10793==> meta_argtypes(activated(relay)).
10794
10795
10796% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3250
10797% [time]
10798% Stopped(Lit(L),time) &
10799% Initiated(Closed(S1),time) &
10800% Initiated(Closed(S2),time) ->
10801% Happens(Light(L),time).
10802% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3254
10803axiom(happens(light(l), Time),
10804   
10805    [ stopped(lit(l), Time),
10806      initiated(closed(s1), Time),
10807      initiated(closed(s2), Time)
10808    ]).
10809
10810
10811% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3256
10812% [time]
10813% Started(Closed(S2),time) &
10814% Initiated(Activated(R),time) ->
10815% Happens(Open(S2),time).
10816% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3259
10817axiom(happens(open(s2), Time),
10818    [started(closed(s2), Time), initiated(activated(r), Time)]).
10819
10820
10821% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3261
10822% [time]
10823% Stopped(Activated(R),time) &
10824% Initiated(Closed(S1),time) &
10825% Initiated(Closed(S3),time) ->
10826% Happens(Activate(R),time).
10827% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3265
10828axiom(happens(activate(r), Time),
10829   
10830    [ stopped(activated(r), Time),
10831      initiated(closed(s1), Time),
10832      initiated(closed(s3), Time)
10833    ]).
10834
10835
10836% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3267
10837% [switch,time]
10838 % Initiates(Close(switch),Closed(switch),time).
10839axiom(initiates(close(Switch), closed(Switch), Time),
10840    []).
10841
10842
10843% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3268
10844% [switch,time]
10845 % Terminates(Open(switch),Closed(switch),time).
10846axiom(terminates(open(Switch), closed(Switch), Time),
10847    []).
10848
10849
10850% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3269
10851% [relay,time]
10852 % Initiates(Activate(relay),Activated(relay),time).
10853axiom(initiates(activate(Relay), activated(Relay), Time),
10854    []).
10855
10856
10857% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3270
10858% [light,time]
10859 % Initiates(Light(light),Lit(light),time).
10860axiom(initiates(light(Light), lit(Light), Time),
10861    []).
10862
10863
10864% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3272
10865% !HoldsAt(Closed(S1),0).
10866 %  not(initially(closed(s1))).
10867axiom(not(initially(closed(s1))),
10868    []).
10869
10870
10871% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3273
10872% HoldsAt(Closed(S2),0).
10873axiom(initially(closed(s2)),
10874    []).
10875
10876
10877% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3274
10878% HoldsAt(Closed(S3),0).
10879axiom(initially(closed(s3)),
10880    []).
10881
10882
10883% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3275
10884% !HoldsAt(Activated(R),0).
10885 %  not(initially(activated(r))).
10886axiom(not(initially(activated(r))),
10887    []).
10888
10889
10890% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3276
10891% !HoldsAt(Lit(L),0).
10892 %  not(initially(lit(l))).
10893axiom(not(initially(lit(l))),
10894    []).
10895
10896
10897% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3278
10898% Happens(Close(S1),0).
10899axiom(happens(close(s1), t),
10900    [is_time(0)]).
10901
10902% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3280
10903% completion Happens
10904% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3281
10905==> completion(happens).
10906
10907% range time 0 1
10908% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3283
10909==> range(time,0,1).
10910
10911% range offset 1 1
10912% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3284
10913==> range(offset,1,1).
10914%; End of file.
10915%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10916%; FILE: examples/Mueller2006/Chapter6/CarryingABook1.e
10917%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10918%;
10919%; Copyright (c) 2005 IBM Corporation and others.
10920%; All rights reserved. This program and the accompanying materials
10921%; are made available under the terms of the Common Public License v1.0
10922%; which accompanies this distribution, and is available at
10923%; http://www.eclipse.org/legal/cpl-v10.html
10924%;
10925%; Contributors:
10926%; IBM - Initial implementation
10927%;
10928%; Example: Carrying a Book (Effect Axioms)
10929%;
10930%; @book{Mueller:2006,
10931%;   author = "Erik T. Mueller",
10932%;   year = "2006",
10933%;   title = "Commonsense Reasoning",
10934%;   address = "San Francisco",
10935%;   publisher = "Morgan Kaufmann/Elsevier",
10936%; }
10937%;
10938%;
10939
10940% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3314
10941% option modeldiff on
10942% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3315
10943:- set_ec_option(modeldiff, on).10944
10945% load foundations/Root.e
10946
10947% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3317
10948% load foundations/EC.e
10949
10950% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3319
10951% sort object
10952% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3320
10953==> sort(object).
10954
10955% sort agent: object
10956% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3321
10957==> subsort(agent,object).
10958
10959% sort room
10960% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3322
10961==> sort(room).
10962
10963% object Book
10964% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3324
10965==> t(object,book).
10966
10967% agent Nathan
10968% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3325
10969==> t(agent,nathan).
10970
10971% room LivingRoom, Kitchen
10972% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3326
10973==> t(room,livingRoom).
10974==> t(room,kitchen).
10975
10976% event LetGoOf(agent,object)
10977 %  event(letGoOf(agent,object)).
10978% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3328
10979==> mpred_prop(letGoOf(agent,object),event).
10980==> meta_argtypes(letGoOf(agent,object)).
10981
10982% event PickUp(agent,object)
10983 %  event(pickUp(agent,object)).
10984% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3329
10985==> mpred_prop(pickUp(agent,object),event).
10986==> meta_argtypes(pickUp(agent,object)).
10987
10988% event Walk(agent,room,room)
10989 %  event(walk(agent,room,room)).
10990% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3330
10991==> mpred_prop(walk(agent,room,room),event).
10992==> meta_argtypes(walk(agent,room,room)).
10993
10994% fluent InRoom(object,room)
10995 %  fluent(inRoom(object,room)).
10996% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3332
10997==> mpred_prop(inRoom(object,room),fluent).
10998==> meta_argtypes(inRoom(object,room)).
10999
11000% fluent Holding(agent,object)
11001 %  fluent(holding(agent,object)).
11002% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3333
11003==> mpred_prop(holding(agent,object),fluent).
11004==> meta_argtypes(holding(agent,object)).
11005
11006
11007% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3334
11008%; Sigma
11009% [agent,room1,room2,time]
11010% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3337
11011% Initiates(Walk(agent,room1,room2),InRoom(agent,room2),time).
11012axiom(initiates(walk(Agent, Room1, Room2), inRoom(Agent, Room2), Time),
11013    []).
11014
11015
11016% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3339
11017% [agent,room1,room2,time]
11018% room1!=% room2 ->
11019% Terminates(Walk(agent,room1,room2),InRoom(agent,room1),time).
11020% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3341
11021axiom(terminates(walk(Agent, Room1, Room2), inRoom(Agent, Room1), Time),
11022    [{dif(Room1, Room2)}]).
11023
11024
11025% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3343
11026% [agent,object,room,time]
11027% HoldsAt(InRoom(agent,room),time) &
11028% HoldsAt(InRoom(object,room),time) ->
11029% Initiates(PickUp(agent,object),Holding(agent,object),time).
11030% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3346
11031axiom(initiates(pickUp(Agent, Object), holding(Agent, Object), Time),
11032   
11033    [ holds_at(inRoom(Agent, Room), Time),
11034      holds_at(inRoom(Object, Room), Time)
11035    ]).
11036
11037
11038% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3348
11039% [agent,object,time]
11040% HoldsAt(Holding(agent,object),time) ->
11041% Terminates(LetGoOf(agent,object),Holding(agent,object),time).
11042% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3350
11043axiom(terminates(letGoOf(Agent, Object), holding(Agent, Object), Time),
11044    [holds_at(holding(Agent, Object), Time)]).
11045
11046
11047% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3352
11048% [agent,object,room1,room2,time]
11049% HoldsAt(Holding(agent,object),time) ->
11050% Initiates(Walk(agent,room1,room2),InRoom(object,room2),time).
11051% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3354
11052axiom(initiates(walk(Agent, Room1, Room2), inRoom(Object, Room2), Time),
11053    [holds_at(holding(Agent, Object), Time)]).
11054
11055
11056% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3356
11057% [agent,object,room1,room2,time]
11058% HoldsAt(Holding(agent,object),time) &
11059% room1!=room2 ->
11060% Terminates(Walk(agent,room1,room2),InRoom(object,room1),time).
11061% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3359
11062axiom(terminates(walk(Agent, Room1, Room2), inRoom(Object, Room1), Time),
11063   
11064    [ holds_at(holding(Agent, Object), Time),
11065      { dif(Room1, Room2)
11066      }
11067    ]).
11068
11069
11070% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3361
11071%; Delta
11072
11073
11074% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3363
11075% Happens(PickUp(Nathan,Book),0).
11076axiom(happens(pickUp(nathan, book), t),
11077    [is_time(0)]).
11078
11079
11080% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3364
11081% Happens(Walk(Nathan,LivingRoom,Kitchen),1).
11082axiom(happens(walk(nathan, livingRoom, kitchen), start),
11083    [is_time(1), b(t, start), ignore(t+1=start)]).
11084
11085
11086% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3366
11087%; Psi
11088% [object,room1,room2,time]
11089% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3369
11090% HoldsAt(InRoom(object,room1),time) &
11091% HoldsAt(InRoom(object,room2),time) ->
11092% room1=room2.
11093% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3371
11094axiom(Room1=Room2,
11095   
11096    [ holds_at(inRoom(Object, Room1), Time),
11097      holds_at(inRoom(Object, Room2), Time)
11098    ]).
11099
11100
11101% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3373
11102%; Gamma
11103
11104
11105% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3375
11106% HoldsAt(InRoom(Nathan,LivingRoom),0).
11107axiom(initially(inRoom(nathan, livingRoom)),
11108    []).
11109
11110
11111% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3376
11112% HoldsAt(InRoom(Book,LivingRoom),0).
11113axiom(initially(inRoom(book, livingRoom)),
11114    []).
11115
11116
11117% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3378
11118%; added:
11119
11120
11121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3379
11122% !HoldsAt(Holding(Nathan,Book),0).
11123 %  not(initially(holding(nathan,book))).
11124axiom(not(initially(holding(nathan, book))),
11125    []).
11126
11127
11128% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3380
11129% [agent,time]
11130 % !HoldsAt(Holding(agent,agent),time).
11131 %  not(holds_at(holding(Agent,Agent),Time)).
11132axiom(not(holds_at(holding(Holding_Param, Holding_Param), Time2)),
11133    []).
11134
11135% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3382
11136% completion Happens
11137% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3383
11138==> completion(happens).
11139
11140% range time 0 2
11141% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3385
11142==> range(time,0,2).
11143
11144% range offset 1 1
11145% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3386
11146==> range(offset,1,1).
11147%; End of file.
11148%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11149%; FILE: examples/Mueller2006/Chapter6/ThielscherCircuit2.e
11150%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11151%;
11152%; Copyright (c) 2005 IBM Corporation and others.
11153%; All rights reserved. This program and the accompanying materials
11154%; are made available under the terms of the Common Public License v1.0
11155%; which accompanies this distribution, and is available at
11156%; http://www.eclipse.org/legal/cpl-v10.html
11157%;
11158%; Contributors:
11159%; IBM - Initial implementation
11160%;
11161%; @article{Thielscher:1997,
11162%;   author = "Michael Thielscher",
11163%;   year = "1997",
11164%;   title = "Ramification and causality",
11165%;   journal = "Artificial Intelligence",
11166%;   volume = "89",
11167%;   pages = "317--364",
11168%; }
11169%;
11170%; @book{Mueller:2006,
11171%;   author = "Erik T. Mueller",
11172%;   year = "2006",
11173%;   title = "Commonsense Reasoning",
11174%;   address = "San Francisco",
11175%;   publisher = "Morgan Kaufmann/Elsevier",
11176%; }
11177%;
11178
11179% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3422
11180% load foundations/Root.e
11181
11182% load foundations/EC.e
11183
11184% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3425
11185% sort switch
11186% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3426
11187==> sort(switch).
11188
11189% sort relay
11190% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3427
11191==> sort(relay).
11192
11193% sort light
11194% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3428
11195==> sort(light).
11196
11197% switch S1, S2, S3
11198% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3430
11199==> t(switch,s1).
11200==> t(switch,s2).
11201==> t(switch,s3).
11202
11203% relay R
11204% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3431
11205==> t(relay,r).
11206
11207% light L
11208% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3432
11209==> t(light,l).
11210
11211% event Light(light)
11212 %  event(light(light)).
11213% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3434
11214==> mpred_prop(light(light),event).
11215==> meta_argtypes(light(light)).
11216
11217% event Unlight(light)
11218 %  event(unlight(light)).
11219% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3435
11220==> mpred_prop(unlight(light),event).
11221==> meta_argtypes(unlight(light)).
11222
11223% event Close(switch)
11224 %  event(close(switch)).
11225% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3436
11226==> mpred_prop(close(switch),event).
11227==> meta_argtypes(close(switch)).
11228
11229% event Open(switch)
11230 %  event(open(switch)).
11231% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3437
11232==> mpred_prop(open(switch),event).
11233==> meta_argtypes(open(switch)).
11234
11235% event Activate(relay)
11236 %  event(activate(relay)).
11237% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3438
11238==> mpred_prop(activate(relay),event).
11239==> meta_argtypes(activate(relay)).
11240
11241% fluent Lit(light)
11242 %  fluent(lit(light)).
11243% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3440
11244==> mpred_prop(lit(light),fluent).
11245==> meta_argtypes(lit(light)).
11246
11247% fluent Closed(switch)
11248 %  fluent(closed(switch)).
11249% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3441
11250==> mpred_prop(closed(switch),fluent).
11251==> meta_argtypes(closed(switch)).
11252
11253% fluent Activated(relay)
11254 %  fluent(activated(relay)).
11255% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3442
11256==> mpred_prop(activated(relay),fluent).
11257==> meta_argtypes(activated(relay)).
11258
11259
11260% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3443
11261% [time]
11262% !HoldsAt(Lit(L),time) &
11263% HoldsAt(Closed(S1),time) &
11264% HoldsAt(Closed(S2),time) ->
11265% Happens(Light(L),time).
11266% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3447
11267axiom(happens(light(l), Time),
11268   
11269    [ not(holds_at(lit(l), Time)),
11270      holds_at(closed(s1), Time),
11271      holds_at(closed(s2), Time)
11272    ]).
11273
11274
11275% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3449
11276% [time]
11277% HoldsAt(Lit(L),time) &
11278% (!HoldsAt(Closed(S1),time) | !HoldsAt(Closed(S2),time)) ->
11279% Happens(Unlight(L),time).
11280% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3452
11281axiom(happens(unlight(l), Time),
11282    [not(holds_at(closed(s1), Time)), holds_at(lit(l), Time)]).
11283axiom(happens(unlight(l), Time),
11284    [not(holds_at(closed(s2), Time)), holds_at(lit(l), Time)]).
11285
11286
11287% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3454
11288% [time]
11289% HoldsAt(Closed(S2),time) &
11290% HoldsAt(Activated(R),time) ->
11291% Happens(Open(S2),time).
11292% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3457
11293axiom(happens(open(s2), Time),
11294    [holds_at(closed(s2), Time), holds_at(activated(r), Time)]).
11295
11296
11297% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3459
11298% [time]
11299% !HoldsAt(Activated(R),time) &
11300% HoldsAt(Closed(S1),time) &
11301% HoldsAt(Closed(S3),time) ->
11302% Happens(Activate(R),time).
11303% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3463
11304axiom(happens(activate(r), Time),
11305   
11306    [ not(holds_at(activated(r), Time)),
11307      holds_at(closed(s1), Time),
11308      holds_at(closed(s3), Time)
11309    ]).
11310
11311
11312% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3465
11313% [switch,time]
11314 % Initiates(Close(switch),Closed(switch),time).
11315axiom(initiates(close(Switch), closed(Switch), Time),
11316    []).
11317
11318
11319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3466
11320% [switch,time]
11321 % Terminates(Open(switch),Closed(switch),time).
11322axiom(terminates(open(Switch), closed(Switch), Time),
11323    []).
11324
11325
11326% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3467
11327% [relay,time]
11328 % Initiates(Activate(relay),Activated(relay),time).
11329axiom(initiates(activate(Relay), activated(Relay), Time),
11330    []).
11331
11332
11333% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3468
11334% [light,time]
11335 % Initiates(Light(light),Lit(light),time).
11336axiom(initiates(light(Light), lit(Light), Time),
11337    []).
11338
11339
11340% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3469
11341% [light,time]
11342 % Terminates(Unlight(light),Lit(light),time).
11343axiom(terminates(unlight(Light), lit(Light), Time),
11344    []).
11345
11346
11347% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3471
11348% !HoldsAt(Closed(S1),0).
11349 %  not(initially(closed(s1))).
11350axiom(not(initially(closed(s1))),
11351    []).
11352
11353
11354% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3472
11355% HoldsAt(Closed(S2),0).
11356axiom(initially(closed(s2)),
11357    []).
11358
11359
11360% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3473
11361% HoldsAt(Closed(S3),0).
11362axiom(initially(closed(s3)),
11363    []).
11364
11365
11366% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3474
11367% !HoldsAt(Activated(R),0).
11368 %  not(initially(activated(r))).
11369axiom(not(initially(activated(r))),
11370    []).
11371
11372
11373% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3475
11374% !HoldsAt(Lit(L),0).
11375 %  not(initially(lit(l))).
11376axiom(not(initially(lit(l))),
11377    []).
11378
11379
11380% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3477
11381% Happens(Close(S1),0).
11382axiom(happens(close(s1), t),
11383    [is_time(0)]).
11384
11385% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3479
11386% completion Happens
11387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3480
11388==> completion(happens).
11389
11390% range time 0 4
11391% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3482
11392==> range(time,0,4).
11393
11394% range offset 1 1
11395% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3483
11396==> range(offset,1,1).
11397%; End of file.
11398%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11399%; FILE: examples/Mueller2006/Chapter6/ShanahanCircuit.e
11400%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11401%;
11402%; Copyright (c) 2005 IBM Corporation and others.
11403%; All rights reserved. This program and the accompanying materials
11404%; are made available under the terms of the Common Public License v1.0
11405%; which accompanies this distribution, and is available at
11406%; http://www.eclipse.org/legal/cpl-v10.html
11407%;
11408%; Contributors:
11409%; IBM - Initial implementation
11410%;
11411%; @inproceedings{Shanahan:1999a,
11412%;   author = "Murray Shanahan",
11413%;   year = "1999",
11414%;   title = "The ramification problem in the event calculus",
11415%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}ixteenth \uppercase{I}nternational \uppercase{J}oint \uppercase{C}onference on \uppercase{A}rtificial \uppercase{I}ntelligence",
11416%;   pages = "140--146",
11417%;   address = "San Mateo, CA",
11418%;   publisher = "Morgan Kaufmann",
11419%; }
11420%;
11421%; @book{Mueller:2006,
11422%;   author = "Erik T. Mueller",
11423%;   year = "2006",
11424%;   title = "Commonsense Reasoning",
11425%;   address = "San Francisco",
11426%;   publisher = "Morgan Kaufmann/Elsevier",
11427%; }
11428%;
11429
11430% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3520
11431% load foundations/Root.e
11432
11433% load foundations/EC.e
11434
11435% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3523
11436% sort switch
11437% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3524
11438==> sort(switch).
11439
11440% sort relay
11441% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3525
11442==> sort(relay).
11443
11444% sort light
11445% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3526
11446==> sort(light).
11447
11448% switch S1, S2, S3
11449% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3528
11450==> t(switch,s1).
11451==> t(switch,s2).
11452==> t(switch,s3).
11453
11454% relay R
11455% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3529
11456==> t(relay,r).
11457
11458% light L
11459% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3530
11460==> t(light,l).
11461
11462% event Light(light)
11463 %  event(light(light)).
11464% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3532
11465==> mpred_prop(light(light),event).
11466==> meta_argtypes(light(light)).
11467
11468% event Unlight(light)
11469 %  event(unlight(light)).
11470% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3533
11471==> mpred_prop(unlight(light),event).
11472==> meta_argtypes(unlight(light)).
11473
11474% event Close(switch)
11475 %  event(close(switch)).
11476% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3534
11477==> mpred_prop(close(switch),event).
11478==> meta_argtypes(close(switch)).
11479
11480% event Open(switch)
11481 %  event(open(switch)).
11482% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3535
11483==> mpred_prop(open(switch),event).
11484==> meta_argtypes(open(switch)).
11485
11486% event Activate(relay)
11487 %  event(activate(relay)).
11488% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3536
11489==> mpred_prop(activate(relay),event).
11490==> meta_argtypes(activate(relay)).
11491
11492% event Deactivate(relay)
11493 %  event(deactivate(relay)).
11494% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3537
11495==> mpred_prop(deactivate(relay),event).
11496==> meta_argtypes(deactivate(relay)).
11497
11498% fluent Lit(light)
11499 %  fluent(lit(light)).
11500% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3539
11501==> mpred_prop(lit(light),fluent).
11502==> meta_argtypes(lit(light)).
11503
11504% fluent Closed(switch)
11505 %  fluent(closed(switch)).
11506% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3540
11507==> mpred_prop(closed(switch),fluent).
11508==> meta_argtypes(closed(switch)).
11509
11510% fluent Activated(relay)
11511 %  fluent(activated(relay)).
11512% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3541
11513==> mpred_prop(activated(relay),fluent).
11514==> meta_argtypes(activated(relay)).
11515
11516
11517% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3542
11518% [time]
11519% !HoldsAt(Lit(L),time) &
11520% HoldsAt(Closed(S1),time) &
11521% HoldsAt(Closed(S2),time) ->
11522% Happens(Light(L),time).
11523% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3546
11524axiom(happens(light(l), Time),
11525   
11526    [ not(holds_at(lit(l), Time)),
11527      holds_at(closed(s1), Time),
11528      holds_at(closed(s2), Time)
11529    ]).
11530
11531
11532% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3548
11533% [time]
11534% HoldsAt(Lit(L),time) &
11535% (!HoldsAt(Closed(S1),time) | !HoldsAt(Closed(S2),time)) ->
11536% Happens(Unlight(L),time).
11537% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3551
11538axiom(happens(unlight(l), Time),
11539    [not(holds_at(closed(s1), Time)), holds_at(lit(l), Time)]).
11540axiom(happens(unlight(l), Time),
11541    [not(holds_at(closed(s2), Time)), holds_at(lit(l), Time)]).
11542
11543
11544% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3553
11545% [time]
11546% HoldsAt(Closed(S2),time) &
11547% HoldsAt(Activated(R),time) ->
11548% Happens(Open(S2),time).
11549% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3556
11550axiom(happens(open(s2), Time),
11551    [holds_at(closed(s2), Time), holds_at(activated(r), Time)]).
11552
11553
11554% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3558
11555% [time]
11556% !HoldsAt(Activated(R),time) &
11557% HoldsAt(Closed(S1),time) &
11558% HoldsAt(Closed(S2),time) &
11559% HoldsAt(Closed(S3),time) ->
11560% Happens(Activate(R),time).
11561% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3563
11562axiom(happens(activate(r), Time),
11563   
11564    [ not(holds_at(activated(r), Time)),
11565      holds_at(closed(s1), Time),
11566      holds_at(closed(s2), Time),
11567      holds_at(closed(s3), Time)
11568    ]).
11569
11570
11571% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3565
11572% [time]
11573% HoldsAt(Activated(R),time) &
11574% (!HoldsAt(Closed(S1),time) |
11575%  !HoldsAt(Closed(S2),time) |
11576%  !HoldsAt(Closed(S3),time)) ->
11577% Happens(Deactivate(R),time).
11578% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3570
11579axiom(happens(deactivate(r), Time),
11580    [not(holds_at(closed(s1), Time)), holds_at(activated(r), Time)]).
11581axiom(happens(deactivate(r), Time),
11582    [not(holds_at(closed(s2), Time)), holds_at(activated(r), Time)]).
11583axiom(happens(deactivate(r), Time),
11584    [not(holds_at(closed(s3), Time)), holds_at(activated(r), Time)]).
11585
11586
11587% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3572
11588% [switch,time]
11589 % Initiates(Close(switch),Closed(switch),time).
11590axiom(initiates(close(Switch), closed(Switch), Time),
11591    []).
11592
11593
11594% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3573
11595% [switch,time]
11596 % Terminates(Open(switch),Closed(switch),time).
11597axiom(terminates(open(Switch), closed(Switch), Time),
11598    []).
11599
11600
11601% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3574
11602% [relay,time]
11603 % Initiates(Activate(relay),Activated(relay),time).
11604axiom(initiates(activate(Relay), activated(Relay), Time),
11605    []).
11606
11607
11608% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3575
11609% [relay,time]
11610 % Terminates(Deactivate(relay),Activated(relay),time).
11611axiom(terminates(deactivate(Relay), activated(Relay), Time),
11612    []).
11613
11614
11615% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3576
11616% [light,time]
11617 % Initiates(Light(light),Lit(light),time).
11618axiom(initiates(light(Light), lit(Light), Time),
11619    []).
11620
11621
11622% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3577
11623% [light,time]
11624 % Terminates(Unlight(light),Lit(light),time).
11625axiom(terminates(unlight(Light), lit(Light), Time),
11626    []).
11627
11628
11629% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3579
11630% !HoldsAt(Closed(S1),0).
11631 %  not(initially(closed(s1))).
11632axiom(not(initially(closed(s1))),
11633    []).
11634
11635
11636% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3580
11637% HoldsAt(Closed(S2),0).
11638axiom(initially(closed(s2)),
11639    []).
11640
11641
11642% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3581
11643% HoldsAt(Closed(S3),0).
11644axiom(initially(closed(s3)),
11645    []).
11646
11647
11648% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3582
11649% !HoldsAt(Activated(R),0).
11650 %  not(initially(activated(r))).
11651axiom(not(initially(activated(r))),
11652    []).
11653
11654
11655% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3583
11656% !HoldsAt(Lit(L),0).
11657 %  not(initially(lit(l))).
11658axiom(not(initially(lit(l))),
11659    []).
11660
11661
11662% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3585
11663% Happens(Close(S1),0).
11664axiom(happens(close(s1), t),
11665    [is_time(0)]).
11666
11667% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3587
11668% completion Happens
11669% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3588
11670==> completion(happens).
11671
11672% range time 0 4
11673% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3590
11674==> range(time,0,4).
11675
11676% range offset 1 1
11677% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3591
11678==> range(offset,1,1).
11679%; End of file.
11680%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11681%; FILE: examples/Mueller2006/Chapter6/CarryingABook2.e
11682%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11683%;
11684%; Copyright (c) 2005 IBM Corporation and others.
11685%; All rights reserved. This program and the accompanying materials
11686%; are made available under the terms of the Common Public License v1.0
11687%; which accompanies this distribution, and is available at
11688%; http://www.eclipse.org/legal/cpl-v10.html
11689%;
11690%; Contributors:
11691%; IBM - Initial implementation
11692%;
11693%; Example: Carrying a Book (Release Axioms and State Constraints)
11694%;
11695%; @book{Mueller:2006,
11696%;   author = "Erik T. Mueller",
11697%;   year = "2006",
11698%;   title = "Commonsense Reasoning",
11699%;   address = "San Francisco",
11700%;   publisher = "Morgan Kaufmann/Elsevier",
11701%; }
11702%;
11703
11704% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3620
11705% load foundations/Root.e
11706
11707% load foundations/EC.e
11708
11709% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3623
11710% sort object
11711% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3624
11712==> sort(object).
11713
11714% sort agent: object
11715% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3625
11716==> subsort(agent,object).
11717
11718% sort room
11719% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3626
11720==> sort(room).
11721
11722% object Book
11723% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3628
11724==> t(object,book).
11725
11726% agent Nathan
11727% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3629
11728==> t(agent,nathan).
11729
11730% room LivingRoom, Kitchen
11731% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3630
11732==> t(room,livingRoom).
11733==> t(room,kitchen).
11734
11735% event LetGoOf(agent,object)
11736 %  event(letGoOf(agent,object)).
11737% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3632
11738==> mpred_prop(letGoOf(agent,object),event).
11739==> meta_argtypes(letGoOf(agent,object)).
11740
11741% event PickUp(agent,object)
11742 %  event(pickUp(agent,object)).
11743% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3633
11744==> mpred_prop(pickUp(agent,object),event).
11745==> meta_argtypes(pickUp(agent,object)).
11746
11747% event Walk(agent,room,room)
11748 %  event(walk(agent,room,room)).
11749% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3634
11750==> mpred_prop(walk(agent,room,room),event).
11751==> meta_argtypes(walk(agent,room,room)).
11752
11753% fluent InRoom(object,room)
11754 %  fluent(inRoom(object,room)).
11755% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3636
11756==> mpred_prop(inRoom(object,room),fluent).
11757==> meta_argtypes(inRoom(object,room)).
11758
11759% fluent Holding(agent,object)
11760 %  fluent(holding(agent,object)).
11761% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3637
11762==> mpred_prop(holding(agent,object),fluent).
11763==> meta_argtypes(holding(agent,object)).
11764
11765
11766% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3638
11767%; Sigma
11768% [agent,room1,room2,time]
11769% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3641
11770% Initiates(Walk(agent,room1,room2),InRoom(agent,room2),time).
11771axiom(initiates(walk(Agent, Room1, Room2), inRoom(Agent, Room2), Time),
11772    []).
11773
11774
11775% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3643
11776% [agent,room1,room2,time]
11777% room1!=% room2 ->
11778% Terminates(Walk(agent,room1,room2),InRoom(agent,room1),time).
11779% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3645
11780axiom(terminates(walk(Agent, Room1, Room2), inRoom(Agent, Room1), Time),
11781    [{dif(Room1, Room2)}]).
11782
11783
11784% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3647
11785% [agent,object,room,time]
11786% HoldsAt(InRoom(agent,room),time) &
11787% HoldsAt(InRoom(object,room),time) ->
11788% Initiates(PickUp(agent,object),Holding(agent,object),time).
11789% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3650
11790axiom(initiates(pickUp(Agent, Object), holding(Agent, Object), Time),
11791   
11792    [ holds_at(inRoom(Agent, Room), Time),
11793      holds_at(inRoom(Object, Room), Time)
11794    ]).
11795
11796
11797% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3652
11798% [agent,object,time]
11799% HoldsAt(Holding(agent,object),time) ->
11800% Terminates(LetGoOf(agent,object),Holding(agent,object),time).
11801% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3654
11802axiom(terminates(letGoOf(Agent, Object), holding(Agent, Object), Time),
11803    [holds_at(holding(Agent, Object), Time)]).
11804
11805
11806% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3656
11807% [agent,object,room,time]
11808% Releases(PickUp(agent,object),InRoom(object,room),time).
11809% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3657
11810axiom(releases(pickUp(Agent, Object), inRoom(Object, Room), Time),
11811    []).
11812
11813
11814% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3659
11815% [agent,object,room,time]
11816% HoldsAt(InRoom(agent,room),time) ->
11817% Initiates(LetGoOf(agent,object),InRoom(object,room),time).
11818% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3661
11819axiom(initiates(letGoOf(Agent, Object), inRoom(Object, Room), Time),
11820    [holds_at(inRoom(Agent, Room), Time)]).
11821
11822
11823% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3663
11824%; Delta
11825
11826
11827% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3665
11828% Happens(PickUp(Nathan,Book),0).
11829axiom(happens(pickUp(nathan, book), t),
11830    [is_time(0)]).
11831
11832
11833% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3666
11834% Happens(Walk(Nathan,LivingRoom,Kitchen),1).
11835axiom(happens(walk(nathan, livingRoom, kitchen), start),
11836    [is_time(1), b(t, start), ignore(t+1=start)]).
11837
11838
11839% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3668
11840%; Psi
11841% [object,room1,room2,time]
11842% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3671
11843% HoldsAt(InRoom(object,room1),time) &
11844% HoldsAt(InRoom(object,room2),time) ->
11845% room1=room2.
11846% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3673
11847axiom(Room1=Room2,
11848   
11849    [ holds_at(inRoom(Object, Room1), Time),
11850      holds_at(inRoom(Object, Room2), Time)
11851    ]).
11852
11853
11854% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3675
11855% [agent,object,room,time]
11856% HoldsAt(Holding(agent,object),time) &
11857% HoldsAt(InRoom(agent,room),time) ->
11858% HoldsAt(InRoom(object,room),time).
11859% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3678
11860axiom(holds_at(inRoom(Object, Room), Time),
11861   
11862    [ holds_at(holding(Agent, Object), Time),
11863      holds_at(inRoom(Agent, Room), Time)
11864    ]).
11865
11866
11867% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3680
11868%; Gamma
11869
11870
11871% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3682
11872% HoldsAt(InRoom(Nathan,LivingRoom),0).
11873axiom(initially(inRoom(nathan, livingRoom)),
11874    []).
11875
11876
11877% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3683
11878% HoldsAt(InRoom(Book,LivingRoom),0).
11879axiom(initially(inRoom(book, livingRoom)),
11880    []).
11881
11882
11883% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3685
11884%; added:
11885
11886
11887% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3686
11888% !HoldsAt(Holding(Nathan,Book),0).
11889 %  not(initially(holding(nathan,book))).
11890axiom(not(initially(holding(nathan, book))),
11891    []).
11892
11893
11894% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3687
11895% [agent,time]
11896 % !HoldsAt(Holding(agent,agent),time).
11897 %  not(holds_at(holding(Agent,Agent),Time)).
11898axiom(not(holds_at(holding(Holding_Param, Holding_Param), Time2)),
11899    []).
11900
11901% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3689
11902% completion Happens
11903% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3690
11904==> completion(happens).
11905
11906% range time 0 2
11907% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3692
11908==> range(time,0,2).
11909
11910% range offset 1 1
11911% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3693
11912==> range(offset,1,1).
11913%; End of file.
11914%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11915%; FILE: examples/Mueller2006/Chapter7/HotAirBalloon.e
11916%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
11917%;
11918%; Copyright (c) 2005 IBM Corporation and others.
11919%; All rights reserved. This program and the accompanying materials
11920%; are made available under the terms of the Common Public License v1.0
11921%; which accompanies this distribution, and is available at
11922%; http://www.eclipse.org/legal/cpl-v10.html
11923%;
11924%; Contributors:
11925%; IBM - Initial implementation
11926%;
11927%; @article{MillerShanahan:1999,
11928%;   author = "Rob Miller and Murray Shanahan",
11929%;   year = "1999",
11930%;   title = "The event calculus in classical logic---\uppercase{A}lternative axiomatisations",
11931%;   journal = "Link{\"{o}}ping Electronic Articles in Computer and Information Science",
11932%;   volume = "4",
11933%;   number = "016",
11934%; }
11935%;
11936%; @book{Mueller:2006,
11937%;   author = "Erik T. Mueller",
11938%;   year = "2006",
11939%;   title = "Commonsense Reasoning",
11940%;   address = "San Francisco",
11941%;   publisher = "Morgan Kaufmann/Elsevier",
11942%; }
11943%;
11944
11945% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3729
11946% option encoding 3
11947% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3730
11948:- set_ec_option(encoding, 3).11949
11950% option trajectory on
11951% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3731
11952:- set_ec_option(trajectory, on).11953
11954% load foundations/Root.e
11955
11956% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3733
11957% load foundations/EC.e
11958
11959% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3735
11960% sort balloon
11961% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3736
11962==> sort(balloon).
11963
11964% sort agent
11965% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3737
11966==> sort(agent).
11967
11968% sort height: integer
11969% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3738
11970==> subsort(height,integer).
11971
11972% agent Nathan
11973% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3740
11974==> t(agent,nathan).
11975
11976% balloon Balloon
11977% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3741
11978==> t(balloon,balloon).
11979
11980% fluent HeaterOn(balloon)
11981 %  fluent(heaterOn(balloon)).
11982% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3743
11983==> mpred_prop(heaterOn(balloon),fluent).
11984==> meta_argtypes(heaterOn(balloon)).
11985
11986% fluent Height(balloon,height)
11987 %  fluent(height(balloon,height)).
11988% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3744
11989==> mpred_prop(height(balloon,height),fluent).
11990==> meta_argtypes(height(balloon,height)).
11991
11992% noninertial Height
11993% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3745
11994==> noninertial(height).
11995
11996% event TurnOnHeater(agent,balloon)
11997 %  event(turnOnHeater(agent,balloon)).
11998% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3747
11999==> mpred_prop(turnOnHeater(agent,balloon),event).
12000==> meta_argtypes(turnOnHeater(agent,balloon)).
12001
12002% event TurnOffHeater(agent,balloon)
12003 %  event(turnOffHeater(agent,balloon)).
12004% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3748
12005==> mpred_prop(turnOffHeater(agent,balloon),event).
12006==> meta_argtypes(turnOffHeater(agent,balloon)).
12007
12008
12009% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3749
12010%; Sigma
12011% [agent,balloon,time]
12012% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3752
12013% Initiates(TurnOnHeater(agent,balloon),HeaterOn(balloon),time).
12014axiom(initiates(turnOnHeater(Agent, Balloon), heaterOn(Balloon), Time),
12015    []).
12016
12017
12018% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3754
12019% [agent,balloon,time]
12020% Terminates(TurnOffHeater(agent,balloon),HeaterOn(balloon),time).
12021% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3755
12022axiom(terminates(turnOffHeater(Agent, Balloon), heaterOn(Balloon), Time),
12023    []).
12024
12025
12026% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3757
12027%; Delta
12028
12029% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3759
12030% Delta: 
12031next_axiom_uses(delta).
12032 
12033
12034
12035% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3759
12036% Happens(TurnOnHeater(Nathan,Balloon),0).
12037axiom(happens(turnOnHeater(nathan, balloon), t),
12038    [is_time(0)]).
12039
12040% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3760
12041% Delta: 
12042next_axiom_uses(delta).
12043 
12044
12045
12046% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3760
12047% Happens(TurnOffHeater(Nathan,Balloon),2).
12048axiom(happens(turnOffHeater(nathan, balloon), t2),
12049    [is_time(2), b(t, t2), ignore(t+2=t2)]).
12050
12051
12052% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3762
12053%; Psi
12054% [balloon,height1,height2,time]
12055% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3765
12056% HoldsAt(Height(balloon,height1),time) &
12057% HoldsAt(Height(balloon,height2),time) ->
12058% height1=height2.
12059% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3767
12060axiom(Height1=Height2,
12061   
12062    [ holds_at(height(Balloon, Height1), Time),
12063      holds_at(height(Balloon, Height2), Time)
12064    ]).
12065
12066
12067% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3769
12068%; Pi
12069% [balloon,height1,height2,offset,time]
12070% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3772
12071% HoldsAt(Height(balloon,height1),time) &
12072% height2 = (height1 + offset) ->
12073% Trajectory(HeaterOn(balloon),time,Height(balloon,height2),offset).
12074% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3774
12075axiom(trajectory(heaterOn(Balloon), Time, height(Balloon, Height2), Offset),
12076   
12077    [ holds_at(height(Balloon, Height1), Time),
12078      equals(Height2, Height1+Offset)
12079    ]).
12080
12081
12082% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3776
12083% [balloon,height1,height2,offset,time]
12084% HoldsAt(Height(balloon,height1),time) &
12085% height2 = (height1 - offset) ->
12086% AntiTrajectory(HeaterOn(balloon),time,Height(balloon,height2),offset).
12087% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3779
12088axiom(antiTrajectory(heaterOn(Balloon), Time, height(Balloon, Height2), Offset),
12089   
12090    [ holds_at(height(Balloon, Height1), Time),
12091      equals(Height2, Height1-Offset)
12092    ]).
12093
12094
12095% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3781
12096%; Gamma
12097
12098
12099% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3783
12100% HoldsAt(Height(Balloon,0),0).
12101axiom(initially(height(balloon, 0)),
12102    []).
12103
12104
12105% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3785
12106%; added:
12107
12108
12109% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3786
12110% !HoldsAt(HeaterOn(Balloon),0).
12111 %  not(initially(heaterOn(balloon))).
12112axiom(not(initially(heaterOn(balloon))),
12113    []).
12114
12115% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3788
12116% completion Delta Happens
12117% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3789
12118==> completion(delta).
12119==> completion(happens).
12120
12121% range time 0 3
12122% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3791
12123==> range(time,0,3).
12124
12125% range height 0 2
12126% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3792
12127==> range(height,0,2).
12128
12129% range offset 1 2
12130% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3793
12131==> range(offset,1,2).
12132%; End of file.
12133%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
12134%; FILE: examples/Mueller2006/Chapter7/FallingObjectWithEvents.e
12135%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
12136%;
12137%; Copyright (c) 2005 IBM Corporation and others.
12138%; All rights reserved. This program and the accompanying materials
12139%; are made available under the terms of the Common Public License v1.0
12140%; which accompanies this distribution, and is available at
12141%; http://www.eclipse.org/legal/cpl-v10.html
12142%;
12143%; Contributors:
12144%; IBM - Initial implementation
12145%;
12146%; @book{Mueller:2006,
12147%;   author = "Erik T. Mueller",
12148%;   year = "2006",
12149%;   title = "Commonsense Reasoning",
12150%;   address = "San Francisco",
12151%;   publisher = "Morgan Kaufmann/Elsevier",
12152%; }
12153%;
12154
12155% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3820
12156% load foundations/Root.e
12157
12158% load foundations/EC.e
12159
12160% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3823
12161% sort object
12162% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3824
12163==> sort(object).
12164
12165% sort agent
12166% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3825
12167==> sort(agent).
12168
12169% sort height: integer
12170% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3826
12171==> subsort(height,integer).
12172
12173% agent Nathan
12174% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3828
12175==> t(agent,nathan).
12176
12177% object Apple
12178% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3829
12179==> t(object,apple).
12180
12181% fluent Falling(object)
12182 %  fluent(falling(object)).
12183% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3831
12184==> mpred_prop(falling(object),fluent).
12185==> meta_argtypes(falling(object)).
12186
12187% fluent Height(object,height)
12188 %  fluent(height(object,height)).
12189% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3832
12190==> mpred_prop(height(object,height),fluent).
12191==> meta_argtypes(height(object,height)).
12192
12193% event Drop(agent,object)
12194 %  event(drop(agent,object)).
12195% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3834
12196==> mpred_prop(drop(agent,object),event).
12197==> meta_argtypes(drop(agent,object)).
12198
12199% event HitGround(object)
12200 %  event(hitGround(object)).
12201% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3835
12202==> mpred_prop(hitGround(object),event).
12203==> meta_argtypes(hitGround(object)).
12204
12205
12206% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3836
12207%; Sigma
12208% [agent,object,time]
12209% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3839
12210% Initiates(Drop(agent,object),Falling(object),time).
12211axiom(initiates(drop(Agent, Object), falling(Object), Time),
12212    []).
12213
12214
12215% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3841
12216% [agent,object,height,time]
12217% Releases(Drop(agent,object),Height(object,height),time).
12218% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3842
12219axiom(releases(drop(Agent, Object), height(Object, Height), Time),
12220    []).
12221
12222
12223% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3844
12224% [object,time]
12225% Terminates(HitGround(object),Falling(object),time).
12226% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3845
12227axiom(terminates(hitGround(Object), falling(Object), Time),
12228    []).
12229
12230
12231% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3847
12232% [object,height,time]
12233% HoldsAt(Height(object,height),time) ->
12234% Initiates(HitGround(object),Height(object,height),time).
12235% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3849
12236axiom(initiates(hitGround(Object), height(Object, Height), Time),
12237    [holds_at(height(Object, Height), Time)]).
12238
12239
12240% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3851
12241%; Delta
12242
12243% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3853
12244% Delta: 
12245next_axiom_uses(delta).
12246 
12247
12248
12249% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3853
12250% [object,time]
12251% HoldsAt(Falling(object),time) &
12252% HoldsAt(Height(object,0),time) ->
12253% Happens(HitGround(object),time).
12254% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3856
12255axiom(happens(hitGround(Object), Time),
12256   
12257    [ holds_at(falling(Object), Time),
12258      holds_at(height(Object, 0), Time)
12259    ]).
12260
12261% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3858
12262% Delta: 
12263next_axiom_uses(delta).
12264 
12265
12266
12267% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3858
12268% Happens(Drop(Nathan,Apple),0).
12269axiom(happens(drop(nathan, apple), t),
12270    [is_time(0)]).
12271
12272
12273% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3860
12274%; Psi
12275% [object,height1,height2,time]
12276% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3863
12277% HoldsAt(Height(object,height1),time) &
12278% HoldsAt(Height(object,height2),time) ->
12279% height1=height2.
12280% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3865
12281axiom(Height1=Height2,
12282   
12283    [ holds_at(height(Object, Height1), Time),
12284      holds_at(height(Object, Height2), Time)
12285    ]).
12286
12287
12288% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3867
12289%; Pi
12290% [object,height1,height2,offset,time]
12291% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3870
12292% HoldsAt(Height(object,height1),time) &
12293% height2 = (height1 - offset) ->
12294% Trajectory(Falling(object),time,Height(object,height2),offset).
12295% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3872
12296axiom(trajectory(falling(Object), Time, height(Object, Height2), Offset),
12297   
12298    [ holds_at(height(Object, Height1), Time),
12299      equals(Height2, Height1-Offset)
12300    ]).
12301
12302
12303% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3874
12304%; Gamma
12305
12306
12307% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3876
12308% !HoldsAt(Falling(Apple),0).
12309 %  not(initially(falling(apple))).
12310axiom(not(initially(falling(apple))),
12311    []).
12312
12313
12314% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3877
12315% HoldsAt(Height(Apple,3),0).
12316axiom(initially(height(apple, 3)),
12317    []).
12318
12319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3879
12320% completion Delta Happens
12321% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3880
12322==> completion(delta).
12323==> completion(happens).
12324
12325% range time 0 5
12326% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3882
12327==> range(time,0,5).
12328
12329% range height 0 3
12330% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3883
12331==> range(height,0,3).
12332
12333% range offset 1 3
12334% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3884
12335==> range(offset,1,3).
12336%; End of file.
12337%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
12338%; FILE: examples/Mueller2006/Chapter7/FallingObjectWithAntiTrajectory.e
12339%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
12340%;
12341%; Copyright (c) 2005 IBM Corporation and others.
12342%; All rights reserved. This program and the accompanying materials
12343%; are made available under the terms of the Common Public License v1.0
12344%; which accompanies this distribution, and is available at
12345%; http://www.eclipse.org/legal/cpl-v10.html
12346%;
12347%; Contributors:
12348%; IBM - Initial implementation
12349%;
12350%; @book{Mueller:2006,
12351%;   author = "Erik T. Mueller",
12352%;   year = "2006",
12353%;   title = "Commonsense Reasoning",
12354%;   address = "San Francisco",
12355%;   publisher = "Morgan Kaufmann/Elsevier",
12356%; }
12357%;
12358
12359% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3911
12360% option encoding 3
12361% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3912
12362:- set_ec_option(encoding, 3).12363
12364% option trajectory on
12365% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3913
12366:- set_ec_option(trajectory, on).12367
12368% load foundations/Root.e
12369
12370% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3915
12371% load foundations/EC.e
12372
12373% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3917
12374% sort object
12375% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3918
12376==> sort(object).
12377
12378% sort agent
12379% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3919
12380==> sort(agent).
12381
12382% sort height: integer
12383% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3920
12384==> subsort(height,integer).
12385
12386% agent Nathan
12387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3922
12388==> t(agent,nathan).
12389
12390% object Apple
12391% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3923
12392==> t(object,apple).
12393
12394% fluent Falling(object)
12395 %  fluent(falling(object)).
12396% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3925
12397==> mpred_prop(falling(object),fluent).
12398==> meta_argtypes(falling(object)).
12399
12400% fluent Height(object,height)
12401 %  fluent(height(object,height)).
12402% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3926
12403==> mpred_prop(height(object,height),fluent).
12404==> meta_argtypes(height(object,height)).
12405
12406% noninertial Height
12407% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3927
12408==> noninertial(height).
12409
12410% event Drop(agent,object)
12411 %  event(drop(agent,object)).
12412% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3929
12413==> mpred_prop(drop(agent,object),event).
12414==> meta_argtypes(drop(agent,object)).
12415
12416% event HitGround(object)
12417 %  event(hitGround(object)).
12418% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3930
12419==> mpred_prop(hitGround(object),event).
12420==> meta_argtypes(hitGround(object)).
12421
12422
12423% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3931
12424%; Sigma
12425% [agent,object,time]
12426% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3934
12427% Initiates(Drop(agent,object),Falling(object),time).
12428axiom(initiates(drop(Agent, Object), falling(Object), Time),
12429    []).
12430
12431
12432% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3936
12433% [object,time]
12434% Terminates(HitGround(object),Falling(object),time).
12435% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3937
12436axiom(terminates(hitGround(Object), falling(Object), Time),
12437    []).
12438
12439
12440% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3939
12441%; Delta
12442
12443% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3941
12444% Delta: 
12445next_axiom_uses(delta).
12446 
12447
12448
12449% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3941
12450% [object,time]
12451% HoldsAt(Falling(object),time) &
12452% HoldsAt(Height(object,0),time) ->
12453% Happens(HitGround(object),time).
12454% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3944
12455axiom(happens(hitGround(Object), Time),
12456   
12457    [ holds_at(falling(Object), Time),
12458      holds_at(height(Object, 0), Time)
12459    ]).
12460
12461% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3946
12462% Delta: 
12463next_axiom_uses(delta).
12464 
12465
12466
12467% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3946
12468% Happens(Drop(Nathan,Apple),0).
12469axiom(happens(drop(nathan, apple), t),
12470    [is_time(0)]).
12471
12472
12473% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3948
12474%; Psi
12475% [object,height1,height2,time]
12476% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3951
12477% HoldsAt(Height(object,height1),time) &
12478% HoldsAt(Height(object,height2),time) ->
12479% height1=height2.
12480% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3953
12481axiom(Height1=Height2,
12482   
12483    [ holds_at(height(Object, Height1), Time),
12484      holds_at(height(Object, Height2), Time)
12485    ]).
12486
12487
12488% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3955
12489%; Pi
12490% [object,height1,height2,offset,time]
12491% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3958
12492% HoldsAt(Height(object,height1),time) &
12493% height2 = (height1 - offset) ->
12494% Trajectory(Falling(object),time,Height(object,height2),offset).
12495% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3960
12496axiom(trajectory(falling(Object), Time, height(Object, Height2), Offset),
12497   
12498    [ holds_at(height(Object, Height1), Time),
12499      equals(Height2, Height1-Offset)
12500    ]).
12501
12502
12503% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3962
12504% [object,height,offset,time]
12505% HoldsAt(Height(object,height),time) ->
12506% AntiTrajectory(Falling(object),time,Height(object,height),offset).
12507% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3964
12508axiom(antiTrajectory(falling(Object), Time, height(Object, Height), Offset),
12509    [holds_at(height(Object, Height), Time)]).
12510
12511
12512% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3966
12513%; Gamma
12514
12515
12516% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3968
12517% !HoldsAt(Falling(Apple),0).
12518 %  not(initially(falling(apple))).
12519axiom(not(initially(falling(apple))),
12520    []).
12521
12522
12523% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3969
12524% HoldsAt(Height(Apple,3),0).
12525axiom(initially(height(apple, 3)),
12526    []).
12527
12528% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3971
12529% completion Delta Happens
12530% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3972
12531==> completion(delta).
12532==> completion(happens).
12533
12534% range time 0 5
12535% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3974
12536==> range(time,0,5).
12537
12538% range height 0 3
12539% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3975
12540==> range(height,0,3).
12541
12542% range offset 1 3
12543% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:3976
12544==> range(offset,1,3).
12545%; End of file.
12546%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
12547%; FILE: examples/Mueller2006/Chapter3/Telephone2.e
12548%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
12549%;
12550%; Copyright (c) 2005 IBM Corporation and others.
12551%; All rights reserved. This program and the accompanying materials
12552%; are made available under the terms of the Common Public License v1.0
12553%; which accompanies this distribution, and is available at
12554%; http://www.eclipse.org/legal/cpl-v10.html
12555%;
12556%; Contributors:
12557%; IBM - Initial implementation
12558%;
12559%; @book{Mueller:2006,
12560%;   author = "Erik T. Mueller",
12561%;   year = "2006",
12562%;   title = "Commonsense Reasoning",
12563%;   address = "San Francisco",
12564%;   publisher = "Morgan Kaufmann/Elsevier",
12565%; }
12566%;
12567
12568% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4003
12569% load foundations/Root.e
12570
12571% load foundations/EC.e
12572
12573% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4006
12574% sort agent
12575% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4007
12576==> sort(agent).
12577
12578% sort phone
12579% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4008
12580==> sort(phone).
12581
12582% agent Agent1, Agent2
12583% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4010
12584==> t(agent,agent1).
12585==> t(agent,agent2).
12586
12587% phone Phone1, Phone2
12588% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4011
12589==> t(phone,phone1).
12590==> t(phone,phone2).
12591
12592% fluent Ringing(phone,phone)
12593 %  fluent(ringing(phone,phone)).
12594% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4013
12595==> mpred_prop(ringing(phone,phone),fluent).
12596==> meta_argtypes(ringing(phone,phone)).
12597
12598% fluent DialTone(phone)
12599 %  fluent(dialTone(phone)).
12600% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4014
12601==> mpred_prop(dialTone(phone),fluent).
12602==> meta_argtypes(dialTone(phone)).
12603
12604% fluent BusySignal(phone)
12605 %  fluent(busySignal(phone)).
12606% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4015
12607==> mpred_prop(busySignal(phone),fluent).
12608==> meta_argtypes(busySignal(phone)).
12609
12610% fluent Idle(phone)
12611 %  fluent(idle(phone)).
12612% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4016
12613==> mpred_prop(idle(phone),fluent).
12614==> meta_argtypes(idle(phone)).
12615
12616% fluent Connected(phone,phone)
12617 %  fluent(connected(phone,phone)).
12618% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4017
12619==> mpred_prop(connected(phone,phone),fluent).
12620==> meta_argtypes(connected(phone,phone)).
12621
12622% fluent Disconnected(phone)
12623 %  fluent(disconnected(phone)).
12624% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4018
12625==> mpred_prop(disconnected(phone),fluent).
12626==> meta_argtypes(disconnected(phone)).
12627
12628% event PickUp(agent,phone)
12629 %  event(pickUp(agent,phone)).
12630% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4020
12631==> mpred_prop(pickUp(agent,phone),event).
12632==> meta_argtypes(pickUp(agent,phone)).
12633
12634% event SetDown(agent,phone)
12635 %  event(setDown(agent,phone)).
12636% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4021
12637==> mpred_prop(setDown(agent,phone),event).
12638==> meta_argtypes(setDown(agent,phone)).
12639
12640% event Dial(agent,phone,phone)
12641 %  event(dial(agent,phone,phone)).
12642% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4022
12643==> mpred_prop(dial(agent,phone,phone),event).
12644==> meta_argtypes(dial(agent,phone,phone)).
12645
12646
12647% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4023
12648%; Sigma
12649% [agent,phone,time]
12650% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4026
12651% HoldsAt(Idle(phone),time) ->
12652% Initiates(PickUp(agent,phone),DialTone(phone),time).
12653% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4027
12654axiom(initiates(pickUp(Agent, Phone), dialTone(Phone), Time),
12655    [holds_at(idle(Phone), Time)]).
12656
12657
12658% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4029
12659% [agent,phone,time]
12660% HoldsAt(Idle(phone),time) ->
12661% Terminates(PickUp(agent,phone),Idle(phone),time).
12662% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4031
12663axiom(terminates(pickUp(Agent, Phone), idle(Phone), Time),
12664    [holds_at(idle(Phone), Time)]).
12665
12666
12667% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4033
12668% [agent,phone,time]
12669% HoldsAt(DialTone(phone),time) ->
12670% Initiates(SetDown(agent,phone),Idle(phone),time).
12671% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4035
12672axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
12673    [holds_at(dialTone(Phone), Time)]).
12674
12675
12676% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4037
12677% [agent,phone,time]
12678% HoldsAt(DialTone(phone),time) ->
12679% Terminates(SetDown(agent,phone),DialTone(phone),time).
12680% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4039
12681axiom(terminates(setDown(Agent, Phone), dialTone(Phone), Time),
12682    [holds_at(dialTone(Phone), Time)]).
12683
12684
12685% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4041
12686% [agent,phone1,phone2,time]
12687% HoldsAt(DialTone(phone1),time) &
12688% HoldsAt(Idle(phone2),time) ->
12689% Initiates(Dial(agent,phone1,phone2),Ringing(phone1,phone2),time).
12690% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4044
12691axiom(initiates(dial(Agent, Phone1, Phone2), ringing(Phone1, Phone2), Time),
12692   
12693    [ holds_at(dialTone(Phone1), Time),
12694      holds_at(idle(Phone2), Time)
12695    ]).
12696
12697
12698% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4046
12699% [agent,phone1,phone2,time]
12700% HoldsAt(DialTone(phone1),time) &
12701% HoldsAt(Idle(phone2),time) ->
12702% Terminates(Dial(agent,phone1,phone2),DialTone(phone1),time).
12703% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4049
12704axiom(terminates(dial(Agent, Phone1, Phone2), dialTone(Phone1), Time),
12705   
12706    [ holds_at(dialTone(Phone1), Time),
12707      holds_at(idle(Phone2), Time)
12708    ]).
12709
12710
12711% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4051
12712% [agent,phone1,phone2,time]
12713% HoldsAt(DialTone(phone1),time) &
12714% HoldsAt(Idle(phone2),time) ->
12715% Terminates(Dial(agent,phone1,phone2),Idle(phone2),time).
12716% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4054
12717axiom(terminates(dial(Agent, Phone1, Phone2), idle(Phone2), Time),
12718   
12719    [ holds_at(dialTone(Phone1), Time),
12720      holds_at(idle(Phone2), Time)
12721    ]).
12722
12723
12724% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4056
12725% [agent,phone1,phone2,time]
12726% HoldsAt(DialTone(phone1),time) &
12727% !HoldsAt(Idle(phone2),time) ->
12728% Initiates(Dial(agent,phone1,phone2),BusySignal(phone1),time).
12729% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4059
12730axiom(initiates(dial(Agent, Phone1, Phone2), busySignal(Phone1), Time),
12731   
12732    [ holds_at(dialTone(Phone1), Time),
12733      not(holds_at(idle(Phone2), Time))
12734    ]).
12735
12736
12737% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4061
12738% [agent,phone1,phone2,time]
12739% HoldsAt(DialTone(phone1),time) &
12740% !HoldsAt(Idle(phone2),time) ->
12741% Terminates(Dial(agent,phone1,phone2),DialTone(phone1),time).
12742% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4064
12743axiom(terminates(dial(Agent, Phone1, Phone2), dialTone(Phone1), Time),
12744   
12745    [ holds_at(dialTone(Phone1), Time),
12746      not(holds_at(idle(Phone2), Time))
12747    ]).
12748
12749
12750% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4066
12751% [agent,phone,time]
12752% HoldsAt(BusySignal(phone),time) ->
12753% Initiates(SetDown(agent,phone),Idle(phone),time).
12754% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4068
12755axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
12756    [holds_at(busySignal(Phone), Time)]).
12757
12758
12759% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4070
12760% [agent,phone,time]
12761% HoldsAt(BusySignal(phone),time) ->
12762% Terminates(SetDown(agent,phone),BusySignal(phone),time).
12763% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4072
12764axiom(terminates(setDown(Agent, Phone), busySignal(Phone), Time),
12765    [holds_at(busySignal(Phone), Time)]).
12766
12767
12768% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4074
12769% [agent,phone1,phone2,time]
12770% HoldsAt(Ringing(phone1,phone2),time) ->
12771% Initiates(SetDown(agent,phone1),Idle(phone1),time).
12772% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4076
12773axiom(initiates(setDown(Agent, Phone1), idle(Phone1), Time),
12774    [holds_at(ringing(Phone1, Phone2), Time)]).
12775
12776
12777% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4078
12778% [agent,phone1,phone2,time]
12779% HoldsAt(Ringing(phone1,phone2),time) ->
12780% Initiates(SetDown(agent,phone1),Idle(phone2),time).
12781% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4080
12782axiom(initiates(setDown(Agent, Phone1), idle(Phone2), Time),
12783    [holds_at(ringing(Phone1, Phone2), Time)]).
12784
12785
12786% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4082
12787% [agent,phone1,phone2,time]
12788% HoldsAt(Ringing(phone1,phone2),time) ->
12789% Terminates(SetDown(agent,phone1),Ringing(phone1,phone2),time).
12790% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4084
12791axiom(terminates(setDown(Agent, Phone1), ringing(Phone1, Phone2), Time),
12792    [holds_at(ringing(Phone1, Phone2), Time)]).
12793
12794
12795% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4086
12796% [agent,phone1,phone2,time]
12797% HoldsAt(Ringing(phone1,phone2),time) ->
12798% Initiates(PickUp(agent,phone2),Connected(phone1,phone2),time).
12799% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4088
12800axiom(initiates(pickUp(Agent, Phone2), connected(Phone1, Phone2), Time),
12801    [holds_at(ringing(Phone1, Phone2), Time)]).
12802
12803
12804% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4090
12805% [agent,phone1,phone2,time]
12806% HoldsAt(Ringing(phone1,phone2),time) ->
12807% Terminates(PickUp(agent,phone2),Ringing(phone1,phone2),time).
12808% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4092
12809axiom(terminates(pickUp(Agent, Phone2), ringing(Phone1, Phone2), Time),
12810    [holds_at(ringing(Phone1, Phone2), Time)]).
12811
12812
12813% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4094
12814% [agent,phone1,phone2,time]
12815% HoldsAt(Connected(phone1,phone2),time) ->
12816% Initiates(SetDown(agent,phone1),Idle(phone1),time).
12817% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4096
12818axiom(initiates(setDown(Agent, Phone1), idle(Phone1), Time),
12819    [holds_at(connected(Phone1, Phone2), Time)]).
12820
12821
12822% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4098
12823% [agent,phone1,phone2,time]
12824% HoldsAt(Connected(phone1,phone2),time) ->
12825% Initiates(SetDown(agent,phone1),Disconnected(phone2),time).
12826% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4100
12827axiom(initiates(setDown(Agent, Phone1), disconnected(Phone2), Time),
12828    [holds_at(connected(Phone1, Phone2), Time)]).
12829
12830
12831% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4102
12832% [agent,phone1,phone2,time]
12833% HoldsAt(Connected(phone1,phone2),time) ->
12834% Terminates(SetDown(agent,phone1),Connected(phone1,phone2),time).
12835% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4104
12836axiom(terminates(setDown(Agent, Phone1), connected(Phone1, Phone2), Time),
12837    [holds_at(connected(Phone1, Phone2), Time)]).
12838
12839
12840% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4106
12841% [agent,phone1,phone2,time]
12842% HoldsAt(Connected(phone1,phone2),time) ->
12843% Initiates(SetDown(agent,phone2),Idle(phone2),time).
12844% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4108
12845axiom(initiates(setDown(Agent, Phone2), idle(Phone2), Time),
12846    [holds_at(connected(Phone1, Phone2), Time)]).
12847
12848
12849% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4110
12850% [agent,phone1,phone2,time]
12851% HoldsAt(Connected(phone1,phone2),time) ->
12852% Initiates(SetDown(agent,phone2),Disconnected(phone1),time).
12853% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4112
12854axiom(initiates(setDown(Agent, Phone2), disconnected(Phone1), Time),
12855    [holds_at(connected(Phone1, Phone2), Time)]).
12856
12857
12858% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4114
12859% [agent,phone1,phone2,time]
12860% HoldsAt(Connected(phone1,phone2),time) ->
12861% Terminates(SetDown(agent,phone2),Connected(phone1,phone2),time).
12862% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4116
12863axiom(terminates(setDown(Agent, Phone2), connected(Phone1, Phone2), Time),
12864    [holds_at(connected(Phone1, Phone2), Time)]).
12865
12866
12867% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4118
12868% [agent,phone,time]
12869% HoldsAt(Disconnected(phone),time) ->
12870% Initiates(SetDown(agent,phone),Idle(phone),time).
12871% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4120
12872axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
12873    [holds_at(disconnected(Phone), Time)]).
12874
12875
12876% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4122
12877% [agent,phone,time]
12878% HoldsAt(Disconnected(phone),time) ->
12879% Terminates(SetDown(agent,phone),Disconnected(phone),time).
12880% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4124
12881axiom(terminates(setDown(Agent, Phone), disconnected(Phone), Time),
12882    [holds_at(disconnected(Phone), Time)]).
12883
12884
12885% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4126
12886%; Delta
12887
12888
12889% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4128
12890% Happens(PickUp(Agent1,Phone1),0).
12891axiom(happens(pickUp(agent1, phone1), t),
12892    [is_time(0)]).
12893
12894
12895% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4129
12896% Happens(Dial(Agent1,Phone1,Phone2),1).
12897axiom(happens(dial(agent1, phone1, phone2), start),
12898    [is_time(1), b(t, start), ignore(t+1=start)]).
12899
12900
12901% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4130
12902% Happens(PickUp(Agent2,Phone2),2).
12903axiom(happens(pickUp(agent2, phone2), t2),
12904    [is_time(2), b(t, t2), ignore(t+2=t2)]).
12905
12906
12907% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4132
12908%; Psi
12909% [phone,time]
12910% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4135
12911% !HoldsAt(Ringing(phone,phone),time).
12912 %  not(holds_at(ringing(Phone,Phone),Time)).
12913axiom(not(holds_at(ringing(Ringing_Param, Ringing_Param), Time2)),
12914    []).
12915
12916
12917% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4137
12918% [phone1,phone2,time]
12919% HoldsAt(Ringing(phone1,phone2),time) &
12920% phone1!=phone2 ->
12921% !HoldsAt(Ringing(phone2,phone1),time).
12922% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4140
12923axiom(not(holds_at(ringing(Phone2, Phone1), Time)),
12924   
12925    [ holds_at(ringing(Phone1, Phone2), Time),
12926      dif(Phone1, Phone2)
12927    ]).
12928
12929
12930% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4142
12931% [phone,time]
12932% !HoldsAt(Connected(phone,phone),time).
12933 %  not(holds_at(connected(Phone,Phone),Time)).
12934% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4143
12935axiom(not(holds_at(connected(Connected_Param, Connected_Param), Time2)),
12936    []).
12937
12938
12939% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4145
12940% [phone1,phone2,time]
12941% HoldsAt(Connected(phone1,phone2),time) &
12942% phone1!=phone2 ->
12943% !HoldsAt(Connected(phone2,phone1),time).
12944% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4148
12945axiom(not(holds_at(connected(Phone2, Phone1), Time)),
12946   
12947    [ holds_at(connected(Phone1, Phone2), Time),
12948      dif(Phone1, Phone2)
12949    ]).
12950
12951% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4150
12952% mutex Idle, DialTone, BusySignal, Disconnected
12953% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4151
12954mutex(idle).
12955mutex(dialTone).
12956mutex(busySignal).
12957mutex(disconnected).
12958
12959
12960% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4152
12961% [phone1,phone2,time]
12962% HoldsAt(Idle(phone1),time) ->
12963% !HoldsAt(Ringing(phone1,phone2),time) &
12964% !HoldsAt(Connected(phone1,phone2),time).
12965
12966 /*   if(holds_at(idle(Phone1), Time),
12967          (not(holds_at(ringing(Phone1, Phone2), Time)), not(holds_at(connected(Phone1, Phone2), Time)))).
12968 */
12969
12970 /*  not(holds_at(idle(Ringing_Param), Time3)) :-
12971       (   holds_at(ringing(Ringing_Param, Ringing_Ret), Time3)
12972       ;   holds_at(connected(Ringing_Param, Ringing_Ret), Time3)
12973       ).
12974 */
12975% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4155
12976axiom(not(holds_at(idle(Ringing_Param), Time3)),
12977    [holds_at(ringing(Ringing_Param, Ringing_Ret), Time3)]).
12978axiom(not(holds_at(idle(Ringing_Param), Time3)),
12979    [holds_at(connected(Ringing_Param, Ringing_Ret), Time3)]).
12980
12981 /*  not(holds_at(ringing(Ringing_Param7, Ringing_Ret8), Time6)) :-
12982       holds_at(idle(Ringing_Param7), Time6).
12983 */
12984axiom(not(holds_at(ringing(Ringing_Param7, Ringing_Ret8), Time6)),
12985    [holds_at(idle(Ringing_Param7), Time6)]).
12986
12987 /*  not(holds_at(connected(Connected_Param, Connected_Ret), Time9)) :-
12988       holds_at(idle(Connected_Param), Time9).
12989 */
12990axiom(not(holds_at(connected(Connected_Param, Connected_Ret), Time9)),
12991    [holds_at(idle(Connected_Param), Time9)]).
12992
12993
12994% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4157
12995%; etc.
12996%; Gamma
12997% [phone]
12998 
12999% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4161
13000% HoldsAt(Idle(phone),0).
13001axiom(initially(idle(Phone)),
13002    []).
13003
13004% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4163
13005% completion Happens
13006% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4164
13007==> completion(happens).
13008
13009% range time 0 3
13010% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4166
13011==> range(time,0,3).
13012
13013% range offset 1 1
13014% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4167
13015==> range(offset,1,1).
13016%; End of file.
13017%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
13018%; FILE: examples/Mueller2006/Chapter3/Telephone1.e
13019%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
13020%;
13021%; Copyright (c) 2005 IBM Corporation and others.
13022%; All rights reserved. This program and the accompanying materials
13023%; are made available under the terms of the Common Public License v1.0
13024%; which accompanies this distribution, and is available at
13025%; http://www.eclipse.org/legal/cpl-v10.html
13026%;
13027%; Contributors:
13028%; IBM - Initial implementation
13029%;
13030%; @book{Mueller:2006,
13031%;   author = "Erik T. Mueller",
13032%;   year = "2006",
13033%;   title = "Commonsense Reasoning",
13034%;   address = "San Francisco",
13035%;   publisher = "Morgan Kaufmann/Elsevier",
13036%; }
13037%;
13038
13039% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4194
13040% load foundations/Root.e
13041
13042% load foundations/EC.e
13043
13044% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4197
13045% sort agent
13046% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4198
13047==> sort(agent).
13048
13049% sort phone
13050% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4199
13051==> sort(phone).
13052
13053% agent Agent1, Agent2
13054% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4201
13055==> t(agent,agent1).
13056==> t(agent,agent2).
13057
13058% phone Phone1, Phone2
13059% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4202
13060==> t(phone,phone1).
13061==> t(phone,phone2).
13062
13063% fluent Ringing(phone,phone)
13064 %  fluent(ringing(phone,phone)).
13065% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4204
13066==> mpred_prop(ringing(phone,phone),fluent).
13067==> meta_argtypes(ringing(phone,phone)).
13068
13069% fluent DialTone(phone)
13070 %  fluent(dialTone(phone)).
13071% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4205
13072==> mpred_prop(dialTone(phone),fluent).
13073==> meta_argtypes(dialTone(phone)).
13074
13075% fluent BusySignal(phone)
13076 %  fluent(busySignal(phone)).
13077% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4206
13078==> mpred_prop(busySignal(phone),fluent).
13079==> meta_argtypes(busySignal(phone)).
13080
13081% fluent Idle(phone)
13082 %  fluent(idle(phone)).
13083% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4207
13084==> mpred_prop(idle(phone),fluent).
13085==> meta_argtypes(idle(phone)).
13086
13087% fluent Connected(phone,phone)
13088 %  fluent(connected(phone,phone)).
13089% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4208
13090==> mpred_prop(connected(phone,phone),fluent).
13091==> meta_argtypes(connected(phone,phone)).
13092
13093% fluent Disconnected(phone)
13094 %  fluent(disconnected(phone)).
13095% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4209
13096==> mpred_prop(disconnected(phone),fluent).
13097==> meta_argtypes(disconnected(phone)).
13098
13099% event PickUp(agent,phone)
13100 %  event(pickUp(agent,phone)).
13101% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4211
13102==> mpred_prop(pickUp(agent,phone),event).
13103==> meta_argtypes(pickUp(agent,phone)).
13104
13105% event SetDown(agent,phone)
13106 %  event(setDown(agent,phone)).
13107% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4212
13108==> mpred_prop(setDown(agent,phone),event).
13109==> meta_argtypes(setDown(agent,phone)).
13110
13111% event Dial(agent,phone,phone)
13112 %  event(dial(agent,phone,phone)).
13113% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4213
13114==> mpred_prop(dial(agent,phone,phone),event).
13115==> meta_argtypes(dial(agent,phone,phone)).
13116
13117
13118% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4214
13119%; Sigma
13120% [agent,phone,time]
13121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4217
13122% HoldsAt(Idle(phone),time) ->
13123% Initiates(PickUp(agent,phone),DialTone(phone),time).
13124% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4218
13125axiom(initiates(pickUp(Agent, Phone), dialTone(Phone), Time),
13126    [holds_at(idle(Phone), Time)]).
13127
13128
13129% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4220
13130% [agent,phone,time]
13131% HoldsAt(Idle(phone),time) ->
13132% Terminates(PickUp(agent,phone),Idle(phone),time).
13133% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4222
13134axiom(terminates(pickUp(Agent, Phone), idle(Phone), Time),
13135    [holds_at(idle(Phone), Time)]).
13136
13137
13138% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4224
13139% [agent,phone,time]
13140% HoldsAt(DialTone(phone),time) ->
13141% Initiates(SetDown(agent,phone),Idle(phone),time).
13142% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4226
13143axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
13144    [holds_at(dialTone(Phone), Time)]).
13145
13146
13147% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4228
13148% [agent,phone,time]
13149% HoldsAt(DialTone(phone),time) ->
13150% Terminates(SetDown(agent,phone),DialTone(phone),time).
13151% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4230
13152axiom(terminates(setDown(Agent, Phone), dialTone(Phone), Time),
13153    [holds_at(dialTone(Phone), Time)]).
13154
13155
13156% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4232
13157% [agent,phone1,phone2,time]
13158% HoldsAt(DialTone(phone1),time) &
13159% HoldsAt(Idle(phone2),time) ->
13160% Initiates(Dial(agent,phone1,phone2),Ringing(phone1,phone2),time).
13161% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4235
13162axiom(initiates(dial(Agent, Phone1, Phone2), ringing(Phone1, Phone2), Time),
13163   
13164    [ holds_at(dialTone(Phone1), Time),
13165      holds_at(idle(Phone2), Time)
13166    ]).
13167
13168
13169% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4237
13170% [agent,phone1,phone2,time]
13171% HoldsAt(DialTone(phone1),time) &
13172% HoldsAt(Idle(phone2),time) ->
13173% Terminates(Dial(agent,phone1,phone2),DialTone(phone1),time).
13174% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4240
13175axiom(terminates(dial(Agent, Phone1, Phone2), dialTone(Phone1), Time),
13176   
13177    [ holds_at(dialTone(Phone1), Time),
13178      holds_at(idle(Phone2), Time)
13179    ]).
13180
13181
13182% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4242
13183% [agent,phone1,phone2,time]
13184% HoldsAt(DialTone(phone1),time) &
13185% HoldsAt(Idle(phone2),time) ->
13186% Terminates(Dial(agent,phone1,phone2),Idle(phone2),time).
13187% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4245
13188axiom(terminates(dial(Agent, Phone1, Phone2), idle(Phone2), Time),
13189   
13190    [ holds_at(dialTone(Phone1), Time),
13191      holds_at(idle(Phone2), Time)
13192    ]).
13193
13194
13195% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4247
13196% [agent,phone1,phone2,time]
13197% HoldsAt(DialTone(phone1),time) &
13198% !HoldsAt(Idle(phone2),time) ->
13199% Initiates(Dial(agent,phone1,phone2),BusySignal(phone1),time).
13200% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4250
13201axiom(initiates(dial(Agent, Phone1, Phone2), busySignal(Phone1), Time),
13202   
13203    [ holds_at(dialTone(Phone1), Time),
13204      not(holds_at(idle(Phone2), Time))
13205    ]).
13206
13207
13208% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4252
13209% [agent,phone1,phone2,time]
13210% HoldsAt(DialTone(phone1),time) &
13211% !HoldsAt(Idle(phone2),time) ->
13212% Terminates(Dial(agent,phone1,phone2),DialTone(phone1),time).
13213% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4255
13214axiom(terminates(dial(Agent, Phone1, Phone2), dialTone(Phone1), Time),
13215   
13216    [ holds_at(dialTone(Phone1), Time),
13217      not(holds_at(idle(Phone2), Time))
13218    ]).
13219
13220
13221% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4257
13222% [agent,phone,time]
13223% HoldsAt(BusySignal(phone),time) ->
13224% Initiates(SetDown(agent,phone),Idle(phone),time).
13225% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4259
13226axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
13227    [holds_at(busySignal(Phone), Time)]).
13228
13229
13230% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4261
13231% [agent,phone,time]
13232% HoldsAt(BusySignal(phone),time) ->
13233% Terminates(SetDown(agent,phone),BusySignal(phone),time).
13234% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4263
13235axiom(terminates(setDown(Agent, Phone), busySignal(Phone), Time),
13236    [holds_at(busySignal(Phone), Time)]).
13237
13238
13239% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4265
13240% [agent,phone1,phone2,time]
13241% HoldsAt(Ringing(phone1,phone2),time) ->
13242% Initiates(SetDown(agent,phone1),Idle(phone1),time).
13243% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4267
13244axiom(initiates(setDown(Agent, Phone1), idle(Phone1), Time),
13245    [holds_at(ringing(Phone1, Phone2), Time)]).
13246
13247
13248% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4269
13249% [agent,phone1,phone2,time]
13250% HoldsAt(Ringing(phone1,phone2),time) ->
13251% Initiates(SetDown(agent,phone1),Idle(phone2),time).
13252% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4271
13253axiom(initiates(setDown(Agent, Phone1), idle(Phone2), Time),
13254    [holds_at(ringing(Phone1, Phone2), Time)]).
13255
13256
13257% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4273
13258% [agent,phone1,phone2,time]
13259% HoldsAt(Ringing(phone1,phone2),time) ->
13260% Terminates(SetDown(agent,phone1),Ringing(phone1,phone2),time).
13261% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4275
13262axiom(terminates(setDown(Agent, Phone1), ringing(Phone1, Phone2), Time),
13263    [holds_at(ringing(Phone1, Phone2), Time)]).
13264
13265
13266% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4277
13267% [agent,phone1,phone2,time]
13268% HoldsAt(Ringing(phone1,phone2),time) ->
13269% Initiates(PickUp(agent,phone2),Connected(phone1,phone2),time).
13270% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4279
13271axiom(initiates(pickUp(Agent, Phone2), connected(Phone1, Phone2), Time),
13272    [holds_at(ringing(Phone1, Phone2), Time)]).
13273
13274
13275% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4281
13276% [agent,phone1,phone2,time]
13277% HoldsAt(Ringing(phone1,phone2),time) ->
13278% Terminates(PickUp(agent,phone2),Ringing(phone1,phone2),time).
13279% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4283
13280axiom(terminates(pickUp(Agent, Phone2), ringing(Phone1, Phone2), Time),
13281    [holds_at(ringing(Phone1, Phone2), Time)]).
13282
13283
13284% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4285
13285% [agent,phone1,phone2,time]
13286% HoldsAt(Connected(phone1,phone2),time) ->
13287% Initiates(SetDown(agent,phone1),Idle(phone1),time).
13288% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4287
13289axiom(initiates(setDown(Agent, Phone1), idle(Phone1), Time),
13290    [holds_at(connected(Phone1, Phone2), Time)]).
13291
13292
13293% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4289
13294% [agent,phone1,phone2,time]
13295% HoldsAt(Connected(phone1,phone2),time) ->
13296% Initiates(SetDown(agent,phone1),Disconnected(phone2),time).
13297% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4291
13298axiom(initiates(setDown(Agent, Phone1), disconnected(Phone2), Time),
13299    [holds_at(connected(Phone1, Phone2), Time)]).
13300
13301
13302% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4293
13303% [agent,phone1,phone2,time]
13304% HoldsAt(Connected(phone1,phone2),time) ->
13305% Terminates(SetDown(agent,phone1),Connected(phone1,phone2),time).
13306% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4295
13307axiom(terminates(setDown(Agent, Phone1), connected(Phone1, Phone2), Time),
13308    [holds_at(connected(Phone1, Phone2), Time)]).
13309
13310
13311% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4297
13312% [agent,phone1,phone2,time]
13313% HoldsAt(Connected(phone1,phone2),time) ->
13314% Initiates(SetDown(agent,phone2),Idle(phone2),time).
13315% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4299
13316axiom(initiates(setDown(Agent, Phone2), idle(Phone2), Time),
13317    [holds_at(connected(Phone1, Phone2), Time)]).
13318
13319
13320% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4301
13321% [agent,phone1,phone2,time]
13322% HoldsAt(Connected(phone1,phone2),time) ->
13323% Initiates(SetDown(agent,phone2),Disconnected(phone1),time).
13324% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4303
13325axiom(initiates(setDown(Agent, Phone2), disconnected(Phone1), Time),
13326    [holds_at(connected(Phone1, Phone2), Time)]).
13327
13328
13329% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4305
13330% [agent,phone1,phone2,time]
13331% HoldsAt(Connected(phone1,phone2),time) ->
13332% Terminates(SetDown(agent,phone2),Connected(phone1,phone2),time).
13333% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4307
13334axiom(terminates(setDown(Agent, Phone2), connected(Phone1, Phone2), Time),
13335    [holds_at(connected(Phone1, Phone2), Time)]).
13336
13337
13338% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4309
13339% [agent,phone,time]
13340% HoldsAt(Disconnected(phone),time) ->
13341% Initiates(SetDown(agent,phone),Idle(phone),time).
13342% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4311
13343axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
13344    [holds_at(disconnected(Phone), Time)]).
13345
13346
13347% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4313
13348% [agent,phone,time]
13349% HoldsAt(Disconnected(phone),time) ->
13350% Terminates(SetDown(agent,phone),Disconnected(phone),time).
13351% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4315
13352axiom(terminates(setDown(Agent, Phone), disconnected(Phone), Time),
13353    [holds_at(disconnected(Phone), Time)]).
13354
13355
13356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4317
13357%; Delta
13358
13359% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4319
13360% Delta: 
13361next_axiom_uses(delta).
13362 
13363
13364
13365% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4319
13366% Happens(PickUp(Agent1,Phone1),0).
13367axiom(happens(pickUp(agent1, phone1), t),
13368    [is_time(0)]).
13369
13370% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4320
13371% Delta: 
13372next_axiom_uses(delta).
13373 
13374
13375
13376% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4320
13377% Happens(Dial(Agent1,Phone1,Phone2),1).
13378axiom(happens(dial(agent1, phone1, phone2), start),
13379    [is_time(1), b(t, start), ignore(t+1=start)]).
13380
13381% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4321
13382% Delta: 
13383next_axiom_uses(delta).
13384 
13385
13386
13387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4321
13388% Happens(PickUp(Agent2,Phone2),2).
13389axiom(happens(pickUp(agent2, phone2), t2),
13390    [is_time(2), b(t, t2), ignore(t+2=t2)]).
13391
13392
13393% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4323
13394%; Gamma
13395% [phone]
13396 % HoldsAt(Idle(phone),0).
13397% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4325
13398axiom(initially(idle(Phone)),
13399    []).
13400
13401
13402% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4326
13403% [phone]
13404 % !HoldsAt(DialTone(phone),0).
13405 %  not(initially(dialTone(Phone))).
13406axiom(not(initially(dialTone(DialTone_Ret))),
13407    []).
13408
13409
13410% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4327
13411% [phone]
13412 % !HoldsAt(BusySignal(phone),0).
13413 %  not(initially(busySignal(Phone))).
13414axiom(not(initially(busySignal(BusySignal_Ret))),
13415    []).
13416
13417
13418% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4328
13419% [phone1,phone2]
13420 % !HoldsAt(Ringing(phone1,phone2),0).
13421 %  not(initially(ringing(Phone1,Phone2))).
13422axiom(not(initially(ringing(Ringing_Param, Ringing_Ret))),
13423    []).
13424
13425
13426% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4329
13427% [phone1,phone2]
13428 % !HoldsAt(Connected(phone1,phone2),0).
13429 %  not(initially(connected(Phone1,Phone2))).
13430axiom(not(initially(connected(Connected_Param, Connected_Ret))),
13431    []).
13432
13433
13434% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4330
13435% [phone]
13436 % !HoldsAt(Disconnected(phone),0).
13437 %  not(initially(disconnected(Phone))).
13438axiom(not(initially(disconnected(Disconnected_Ret))),
13439    []).
13440
13441% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4332
13442% completion Delta Happens
13443% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4333
13444==> completion(delta).
13445==> completion(happens).
13446
13447% range time 0 3
13448% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4335
13449==> range(time,0,3).
13450
13451% range offset 1 1
13452% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4336
13453==> range(offset,1,1).
13454%; End of file.
13455%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
13456%; FILE: examples/Mueller2006/Chapter12/DefaultLocation.e
13457%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
13458%;
13459%; Copyright (c) 2005 IBM Corporation and others.
13460%; All rights reserved. This program and the accompanying materials
13461%; are made available under the terms of the Common Public License v1.0
13462%; which accompanies this distribution, and is available at
13463%; http://www.eclipse.org/legal/cpl-v10.html
13464%;
13465%; Contributors:
13466%; IBM - Initial implementation
13467%;
13468%; @book{Mueller:2006,
13469%;   author = "Erik T. Mueller",
13470%;   year = "2006",
13471%;   title = "Commonsense Reasoning",
13472%;   address = "San Francisco",
13473%;   publisher = "Morgan Kaufmann/Elsevier",
13474%; }
13475%;
13476
13477% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4363
13478% load foundations/Root.e
13479
13480% load foundations/EC.e
13481
13482% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4366
13483% sort object
13484% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4367
13485==> sort(object).
13486
13487% sort agent: object
13488% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4368
13489==> subsort(agent,object).
13490
13491% sort device: object
13492% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4369
13493==> subsort(device,object).
13494
13495% sort tv: device
13496% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4370
13497==> subsort(tv,device).
13498
13499% sort room
13500% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4371
13501==> sort(room).
13502
13503% agent Nathan
13504% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4373
13505==> t(agent,nathan).
13506
13507% tv TV
13508% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4374
13509==> t(tv,tv).
13510
13511% room LivingRoom, Kitchen
13512% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4375
13513==> t(room,livingRoom).
13514==> t(room,kitchen).
13515
13516% event TurnOn(agent,device)
13517 %  event(turnOn(agent,device)).
13518% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4377
13519==> mpred_prop(turnOn(agent,device),event).
13520==> meta_argtypes(turnOn(agent,device)).
13521
13522% event Walk(agent,room,room)
13523 %  event(walk(agent,room,room)).
13524% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4378
13525==> mpred_prop(walk(agent,room,room),event).
13526==> meta_argtypes(walk(agent,room,room)).
13527
13528% fluent InRoom(object,room)
13529 %  fluent(inRoom(object,room)).
13530% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4380
13531==> mpred_prop(inRoom(object,room),fluent).
13532==> meta_argtypes(inRoom(object,room)).
13533
13534% fluent On(device)
13535 %  fluent(on(device)).
13536% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4381
13537==> mpred_prop(on(device),fluent).
13538==> meta_argtypes(on(device)).
13539
13540% fluent PluggedIn(device)
13541 %  fluent(pluggedIn(device)).
13542% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4382
13543==> mpred_prop(pluggedIn(device),fluent).
13544==> meta_argtypes(pluggedIn(device)).
13545
13546% fluent BrokenSwitch(device)
13547 %  fluent(brokenSwitch(device)).
13548% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4383
13549==> mpred_prop(brokenSwitch(device),fluent).
13550==> meta_argtypes(brokenSwitch(device)).
13551
13552% predicate Ab1(device,time)
13553 %  predicate(ab1(device,time)).
13554% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4385
13555==> mpred_prop(ab1(device,time),predicate).
13556==> meta_argtypes(ab1(device,time)).
13557
13558% predicate Ab2(room,time)
13559 %  predicate(ab2(room,time)).
13560% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4386
13561==> mpred_prop(ab2(room,time),predicate).
13562==> meta_argtypes(ab2(room,time)).
13563
13564
13565% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4387
13566%; Sigma
13567% [agent,room1,room2,time]
13568% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4390
13569% Initiates(Walk(agent,room1,room2),InRoom(agent,room2),time).
13570axiom(initiates(walk(Agent, Room1, Room2), inRoom(Agent, Room2), Time),
13571    []).
13572
13573
13574% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4392
13575% [agent,room1,room2,time]
13576% room1!=% room2 ->
13577% Terminates(Walk(agent,room1,room2),InRoom(agent,room1),time).
13578% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4394
13579axiom(terminates(walk(Agent, Room1, Room2), inRoom(Agent, Room1), Time),
13580    [{dif(Room1, Room2)}]).
13581
13582
13583% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4396
13584% [agent,device,time]
13585% !Ab1(device,time) ->
13586% Initiates(TurnOn(agent,device),On(device),time).
13587% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4398
13588axiom(initiates(turnOn(Agent, Device), on(Device), Time),
13589    [not(ab1(Device, Time))]).
13590
13591
13592% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4400
13593%; Delta
13594% [agent,room1,room2,time]
13595% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4403
13596% Happens(Walk(agent,room1,room2),time) ->
13597% room1!=room2 &
13598% HoldsAt(InRoom(agent,room1),time).
13599% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4405
13600axiom(requires(walk(Agent, Room1, Room2), Time),
13601   
13602    [ { dif(Room1, Room2)
13603      },
13604      holds_at(inRoom(Agent, Room1), Time)
13605    ]).
13606
13607
13608% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4407
13609% [agent,device,time]
13610% Happens(TurnOn(agent,device),time) ->
13611% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4409
13612% {room}%  HoldsAt(InRoom(agent,room),time) &
13613%        HoldsAt(InRoom(device,room),time).
13614
13615 /*   exists([Room],
13616             if(happens(turnOn(Agent, Device), Time),
13617                 (holds_at(inRoom(Agent, Room), Time), holds_at(inRoom(Device, Room), Time)))).
13618 */
13619
13620 /*  not(some(Some_Param, '$kolem_Fn_354'(Fn_354_Param, InRoom_Param, Maptime))) :-
13621       happens(turnOn(Fn_354_Param, InRoom_Param), Maptime),
13622       (   not(holds_at(inRoom(Fn_354_Param, Some_Param),
13623                        Maptime))
13624       ;   not(holds_at(inRoom(InRoom_Param, Some_Param),
13625                        Maptime))
13626       ).
13627 */
13628% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4410
13629axiom(not(some(Some_Param, '$kolem_Fn_354'(Fn_354_Param, InRoom_Param, Maptime))),
13630   
13631    [ not(holds_at(inRoom(Fn_354_Param, Some_Param), Maptime)),
13632      happens(turnOn(Fn_354_Param, InRoom_Param), Maptime)
13633    ]).
13634axiom(not(some(Some_Param, '$kolem_Fn_354'(Fn_354_Param, InRoom_Param, Maptime))),
13635   
13636    [ not(holds_at(inRoom(InRoom_Param, Some_Param), Maptime)),
13637      happens(turnOn(Fn_354_Param, InRoom_Param), Maptime)
13638    ]).
13639
13640 /*  not(happens(turnOn(TurnOn_Param, InRoom_Param11), Maptime9)) :-
13641       (   not(holds_at(inRoom(TurnOn_Param, Some_Param12),
13642                        Maptime9))
13643       ;   not(holds_at(inRoom(InRoom_Param11, Some_Param12),
13644                        Maptime9))
13645       ),
13646       some(Some_Param12,
13647            '$kolem_Fn_354'(TurnOn_Param, InRoom_Param11, Maptime9)).
13648 */
13649axiom(not(happens(turnOn(TurnOn_Param, InRoom_Param11), Maptime9)),
13650   
13651    [ not(holds_at(inRoom(TurnOn_Param, Some_Param12),
13652                   Maptime9)),
13653      some(Some_Param12,
13654           '$kolem_Fn_354'(TurnOn_Param,
13655                           InRoom_Param11,
13656                           Maptime9))
13657    ]).
13658axiom(not(happens(turnOn(TurnOn_Param, InRoom_Param11), Maptime9)),
13659   
13660    [ not(holds_at(inRoom(InRoom_Param11, Some_Param12),
13661                   Maptime9)),
13662      some(Some_Param12,
13663           '$kolem_Fn_354'(TurnOn_Param,
13664                           InRoom_Param11,
13665                           Maptime9))
13666    ]).
13667
13668 /*  holds_at(inRoom(InRoom_Param14, Some_Param15), Time13) :-
13669       happens(turnOn(InRoom_Param14, TurnOn_Ret), Time13),
13670       some(Some_Param15,
13671            '$kolem_Fn_354'(InRoom_Param14, TurnOn_Ret, Time13)).
13672 */
13673axiom(holds_at(inRoom(InRoom_Param14, Some_Param15), Time13),
13674   
13675    [ happens(turnOn(InRoom_Param14, TurnOn_Ret), Time13),
13676      some(Some_Param15,
13677           '$kolem_Fn_354'(InRoom_Param14, TurnOn_Ret, Time13))
13678    ]).
13679
13680 /*  holds_at(inRoom(InRoom_Param18, Some_Param20), Time17) :-
13681       happens(turnOn(TurnOn_Param19, InRoom_Param18), Time17),
13682       some(Some_Param20,
13683            '$kolem_Fn_354'(TurnOn_Param19, InRoom_Param18, Time17)).
13684 */
13685axiom(holds_at(inRoom(InRoom_Param18, Some_Param20), Time17),
13686   
13687    [ happens(turnOn(TurnOn_Param19, InRoom_Param18), Time17),
13688      some(Some_Param20,
13689           '$kolem_Fn_354'(TurnOn_Param19,
13690                           InRoom_Param18,
13691                           Time17))
13692    ]).
13693
13694
13695% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4412
13696% [event1,event2,time]
13697% Happens(event1,time) &
13698% Happens(event2,time) ->
13699% event1=event2.
13700% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4415
13701axiom(Event1=Event2,
13702    [happens(Event1, Time), happens(Event2, Time)]).
13703
13704
13705% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4417
13706%; Theta
13707
13708% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4419
13709% Theta: 
13710next_axiom_uses(theta).
13711 
13712
13713
13714% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4419
13715% [device,time]
13716 % HoldsAt(BrokenSwitch(device),time) -> Ab1(device,time).
13717axiom(ab1(Device, Time),
13718    [holds_at(brokenSwitch(Device), Time)]).
13719
13720% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4420
13721% Theta: 
13722next_axiom_uses(theta).
13723 
13724
13725
13726% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4420
13727% [device,time]
13728 % !HoldsAt(PluggedIn(device),time) -> Ab1(device,time).
13729axiom(ab1(Device, Time),
13730    [not(holds_at(pluggedIn(Device), Time))]).
13731
13732
13733% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4422
13734%; Psi
13735% [object,room1,room2,time]
13736% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4425
13737% HoldsAt(InRoom(object,room1),time) &
13738% HoldsAt(InRoom(object,room2),time) ->
13739% room1=room2.
13740% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4427
13741axiom(Room1=Room2,
13742   
13743    [ holds_at(inRoom(Object, Room1), Time),
13744      holds_at(inRoom(Object, Room2), Time)
13745    ]).
13746
13747
13748% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4429
13749%; Gamma
13750% [tv]
13751 % !HoldsAt(On(tv),0).
13752 %  not(initially(on(Tv))).
13753% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4431
13754axiom(not(initially(on(On_Ret))),
13755    []).
13756
13757
13758% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4432
13759% [tv]
13760 % !HoldsAt(BrokenSwitch(tv),0).
13761 %  not(initially(brokenSwitch(Tv))).
13762axiom(not(initially(brokenSwitch(BrokenSwitch_Ret))),
13763    []).
13764
13765
13766% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4433
13767% [tv]
13768 % HoldsAt(PluggedIn(tv),0).
13769axiom(initially(pluggedIn(Tv)),
13770    []).
13771
13772
13773% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4435
13774% HoldsAt(InRoom(Nathan,Kitchen),0).
13775axiom(initially(inRoom(nathan, kitchen)),
13776    []).
13777
13778
13779% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4437
13780% [time]
13781% !Ab2(LivingRoom,time) ->
13782% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4439
13783% {tv}%  HoldsAt(InRoom(tv,LivingRoom),time).
13784
13785 /*  exists([Tv],
13786          if(not(ab2(livingRoom,Time)),
13787   	  holds_at(inRoom(Tv,livingRoom),Time))).
13788 */
13789
13790 /*  holds_at(inRoom(InRoom_Param, livingRoom), Time3) :-
13791       not(ab2(livingRoom, Time3)),
13792       some(InRoom_Param, '$kolem_Fn_355'(Time3)).
13793 */
13794axiom(holds_at(inRoom(InRoom_Param, livingRoom), Time3),
13795   
13796    [ not(ab2(livingRoom, Time3)),
13797      some(InRoom_Param, '$kolem_Fn_355'(Time3))
13798    ]).
13799
13800 /*  ab2(livingRoom, Time5) :-
13801       not(holds_at(inRoom(InRoom_Param6, livingRoom), Time5)),
13802       some(InRoom_Param6, '$kolem_Fn_355'(Time5)).
13803 */
13804axiom(ab2(livingRoom, Time5),
13805   
13806    [ not(holds_at(inRoom(InRoom_Param6, livingRoom), Time5)),
13807      some(InRoom_Param6, '$kolem_Fn_355'(Time5))
13808    ]).
13809
13810 /*  not(some(Some_Param, '$kolem_Fn_355'(Time7))) :-
13811       not(holds_at(inRoom(Some_Param, livingRoom), Time7)),
13812       not(ab2(livingRoom, Time7)).
13813 */
13814axiom(not(some(Some_Param, '$kolem_Fn_355'(Time7))),
13815   
13816    [ not(holds_at(inRoom(Some_Param, livingRoom), Time7)),
13817      not(ab2(livingRoom, Time7))
13818    ]).
13819
13820
13821% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4441
13822%; goal
13823% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4443
13824% {tv} 
13825
13826
13827% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4443
13828% Happens(TurnOn(Nathan,tv),1).
13829 %  exists([Tv],happens(turnOn(nathan,Tv),1)).
13830
13831 /*  happens(turnOn(nathan, Some_Param), 1) :-
13832       some(Some_Param, '$kolem_Fn_356').
13833 */
13834axiom(happens(turnOn(nathan, Some_Param), start),
13835    [some(Some_Param, '$kolem_Fn_356'), b(t, start), ignore(t+1=start)]).
13836
13837 /*  not(some(Some_Param3, '$kolem_Fn_356')) :-
13838       not(happens(turnOn(nathan, Some_Param3), 1)).
13839 */
13840axiom(not(some(Some_Param3, '$kolem_Fn_356')),
13841   
13842    [ not(happens(turnOn(nathan, Some_Param3), start)),
13843      b(t, start),
13844      ignore(t+1=start)
13845    ]).
13846
13847
13848% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4445
13849%; for two TVs:
13850%;[tv,time] !HoldsAt(InRoom(tv,Kitchen),time).
13851%;[tv,time] {room} HoldsAt(InRoom(tv,room),time).
13852
13853% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4449
13854% completion Theta Ab1
13855% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4450
13856==> completion(theta).
13857==> completion(ab1).
13858
13859% completion Theta Ab2
13860% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4451
13861==> completion(theta).
13862==> completion(ab2).
13863
13864% range time 0 2
13865% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4453
13866==> range(time,0,2).
13867
13868% range offset 1 1
13869% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4454
13870==> range(offset,1,1).
13871%; End of file.
13872%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
13873%; FILE: examples/Mueller2006/Chapter12/Device.e
13874%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
13875%;
13876%; Copyright (c) 2005 IBM Corporation and others.
13877%; All rights reserved. This program and the accompanying materials
13878%; are made available under the terms of the Common Public License v1.0
13879%; which accompanies this distribution, and is available at
13880%; http://www.eclipse.org/legal/cpl-v10.html
13881%;
13882%; Contributors:
13883%; IBM - Initial implementation
13884%;
13885%; @book{Mueller:2006,
13886%;   author = "Erik T. Mueller",
13887%;   year = "2006",
13888%;   title = "Commonsense Reasoning",
13889%;   address = "San Francisco",
13890%;   publisher = "Morgan Kaufmann/Elsevier",
13891%; }
13892%;
13893
13894% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4481
13895% load foundations/Root.e
13896
13897% load foundations/EC.e
13898
13899% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4484
13900% sort agent
13901% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4485
13902==> sort(agent).
13903
13904% sort device
13905% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4486
13906==> sort(device).
13907
13908% agent Nathan
13909% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4488
13910==> t(agent,nathan).
13911
13912% device Device1, AntiqueDevice1
13913% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4489
13914==> t(device,device1).
13915==> t(device,antiqueDevice1).
13916
13917% predicate Ab1(device,time)
13918 %  predicate(ab1(device,time)).
13919% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4491
13920==> mpred_prop(ab1(device,time),predicate).
13921==> meta_argtypes(ab1(device,time)).
13922
13923% fluent On(device)
13924 %  fluent(on(device)).
13925% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4493
13926==> mpred_prop(on(device),fluent).
13927==> meta_argtypes(on(device)).
13928
13929% fluent PluggedIn(device)
13930 %  fluent(pluggedIn(device)).
13931% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4494
13932==> mpred_prop(pluggedIn(device),fluent).
13933==> meta_argtypes(pluggedIn(device)).
13934
13935% fluent BrokenSwitch(device)
13936 %  fluent(brokenSwitch(device)).
13937% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4495
13938==> mpred_prop(brokenSwitch(device),fluent).
13939==> meta_argtypes(brokenSwitch(device)).
13940
13941% event TurnOn(agent,device)
13942 %  event(turnOn(agent,device)).
13943% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4497
13944==> mpred_prop(turnOn(agent,device),event).
13945==> meta_argtypes(turnOn(agent,device)).
13946
13947
13948% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4498
13949%; Sigma
13950% [agent,device,time]
13951% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4501
13952% !Ab1(device,time) ->
13953% Initiates(TurnOn(agent,device),On(device),time).
13954% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4502
13955axiom(initiates(turnOn(Agent, Device), on(Device), Time),
13956    [not(ab1(Device, Time))]).
13957
13958
13959% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4504
13960%; Delta
13961
13962
13963% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4506
13964% Happens(TurnOn(Nathan,Device1),0).
13965axiom(happens(turnOn(nathan, device1), t),
13966    [is_time(0)]).
13967
13968
13969% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4508
13970%; Theta
13971
13972% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4510
13973% Theta: 
13974next_axiom_uses(theta).
13975 
13976
13977
13978% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4510
13979% [device,time]
13980 % HoldsAt(BrokenSwitch(device),time) -> Ab1(device,time).
13981axiom(ab1(Device, Time),
13982    [holds_at(brokenSwitch(Device), Time)]).
13983
13984% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4511
13985% Theta: 
13986next_axiom_uses(theta).
13987 
13988
13989
13990% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4511
13991% [device,time]
13992 % !HoldsAt(PluggedIn(device),time) -> Ab1(device,time).
13993axiom(ab1(Device, Time),
13994    [not(holds_at(pluggedIn(Device), Time))]).
13995
13996% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4512
13997% Theta: 
13998next_axiom_uses(theta).
13999 
14000
14001
14002% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4512
14003% [time]
14004 % Ab1(AntiqueDevice1,time).
14005ab1(antiqueDevice1,Time).
14006
14007
14008% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4514
14009%; Gamma
14010
14011
14012% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4516
14013% !HoldsAt(On(Device1),0).
14014 %  not(initially(on(device1))).
14015axiom(not(initially(on(device1))),
14016    []).
14017
14018
14019% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4517
14020% !HoldsAt(BrokenSwitch(Device1),0).
14021 %  not(initially(brokenSwitch(device1))).
14022axiom(not(initially(brokenSwitch(device1))),
14023    []).
14024
14025
14026% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4518
14027% HoldsAt(PluggedIn(Device1),0).
14028axiom(initially(pluggedIn(device1)),
14029    []).
14030
14031
14032% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4520
14033%; added:
14034% [time]
14035 % !HoldsAt(On(AntiqueDevice1),time).
14036 %  not(holds_at(on(antiqueDevice1),Time)).
14037% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4521
14038axiom(not(holds_at(on(antiqueDevice1), Time1)),
14039    []).
14040
14041
14042% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4522
14043% [time]
14044 % HoldsAt(PluggedIn(AntiqueDevice1),time).
14045holds_at(pluggedIn(antiqueDevice1),Time).
14046
14047
14048% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4524
14049%; entailed:
14050%; HoldsAt(On(Device1),1).
14051
14052% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4527
14053% completion Theta Ab1
14054% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4528
14055==> completion(theta).
14056==> completion(ab1).
14057
14058% completion Happens
14059% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4529
14060==> completion(happens).
14061
14062% range time 0 1
14063% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4531
14064==> range(time,0,1).
14065
14066% range offset 1 1
14067% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4532
14068==> range(offset,1,1).
14069%; End of file.
14070%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14071%; FILE: examples/Mueller2006/Chapter12/ErraticDevice.e
14072%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14073%;
14074%; Copyright (c) 2005 IBM Corporation and others.
14075%; All rights reserved. This program and the accompanying materials
14076%; are made available under the terms of the Common Public License v1.0
14077%; which accompanies this distribution, and is available at
14078%; http://www.eclipse.org/legal/cpl-v10.html
14079%;
14080%; Contributors:
14081%; IBM - Initial implementation
14082%;
14083%; @book{Mueller:2006,
14084%;   author = "Erik T. Mueller",
14085%;   year = "2006",
14086%;   title = "Commonsense Reasoning",
14087%;   address = "San Francisco",
14088%;   publisher = "Morgan Kaufmann/Elsevier",
14089%; }
14090%;
14091
14092% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4559
14093% load foundations/Root.e
14094
14095% load foundations/EC.e
14096
14097% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4562
14098% sort agent
14099% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4563
14100==> sort(agent).
14101
14102% sort device
14103% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4564
14104==> sort(device).
14105
14106% agent Nathan
14107% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4566
14108==> t(agent,nathan).
14109
14110% device Device1
14111% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4567
14112==> t(device,device1).
14113
14114% predicate Ab1(device,time)
14115 %  predicate(ab1(device,time)).
14116% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4569
14117==> mpred_prop(ab1(device,time),predicate).
14118==> meta_argtypes(ab1(device,time)).
14119
14120% fluent On(device)
14121 %  fluent(on(device)).
14122% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4571
14123==> mpred_prop(on(device),fluent).
14124==> meta_argtypes(on(device)).
14125
14126% fluent PluggedIn(device)
14127 %  fluent(pluggedIn(device)).
14128% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4572
14129==> mpred_prop(pluggedIn(device),fluent).
14130==> meta_argtypes(pluggedIn(device)).
14131
14132% fluent BrokenSwitch(device)
14133 %  fluent(brokenSwitch(device)).
14134% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4573
14135==> mpred_prop(brokenSwitch(device),fluent).
14136==> meta_argtypes(brokenSwitch(device)).
14137
14138% fluent Erratic(device)
14139 %  fluent(erratic(device)).
14140% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4574
14141==> mpred_prop(erratic(device),fluent).
14142==> meta_argtypes(erratic(device)).
14143
14144% fluent DeterminingFluent(device)
14145 %  fluent(determiningFluent(device)).
14146% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4576
14147==> mpred_prop(determiningFluent(device),fluent).
14148==> meta_argtypes(determiningFluent(device)).
14149
14150% noninertial DeterminingFluent
14151% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4577
14152==> noninertial(determiningFluent).
14153
14154% event TurnOn(agent,device)
14155 %  event(turnOn(agent,device)).
14156% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4579
14157==> mpred_prop(turnOn(agent,device),event).
14158==> meta_argtypes(turnOn(agent,device)).
14159
14160
14161% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4580
14162%; Sigma
14163% [agent,device,time]
14164% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4583
14165% !Ab1(device,time) ->
14166% Initiates(TurnOn(agent,device),On(device),time).
14167% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4584
14168axiom(initiates(turnOn(Agent, Device), on(Device), Time),
14169    [not(ab1(Device, Time))]).
14170
14171
14172% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4586
14173%; Delta
14174
14175
14176% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4588
14177% Happens(TurnOn(Nathan,Device1),0).
14178axiom(happens(turnOn(nathan, device1), t),
14179    [is_time(0)]).
14180
14181
14182% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4590
14183%; Theta
14184
14185% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4593
14186% Theta: 
14187next_axiom_uses(theta).
14188 
14189
14190
14191% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4593
14192% [device,time]
14193 % HoldsAt(BrokenSwitch(device),time) -> Ab1(device,time).
14194axiom(ab1(Device, Time),
14195    [holds_at(brokenSwitch(Device), Time)]).
14196
14197% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4594
14198% Theta: 
14199next_axiom_uses(theta).
14200 
14201
14202
14203% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4594
14204% [device,time]
14205% HoldsAt(Erratic(device),time) & HoldsAt(DeterminingFluent(device),time) ->
14206% Ab1(device,time).
14207% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4596
14208axiom(ab1(Device, Time),
14209   
14210    [ holds_at(erratic(Device), Time),
14211      holds_at(determiningFluent(Device), Time)
14212    ]).
14213
14214% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4598
14215% Theta: 
14216next_axiom_uses(theta).
14217 
14218
14219
14220% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4598
14221% [device,time]
14222 % !HoldsAt(PluggedIn(device),time) -> Ab1(device,time).
14223axiom(ab1(Device, Time),
14224    [not(holds_at(pluggedIn(Device), Time))]).
14225
14226
14227% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4600
14228%; Gamma
14229
14230
14231% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4602
14232% !HoldsAt(On(Device1),0).
14233 %  not(initially(on(device1))).
14234axiom(not(initially(on(device1))),
14235    []).
14236
14237
14238% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4603
14239% !HoldsAt(BrokenSwitch(Device1),0).
14240 %  not(initially(brokenSwitch(device1))).
14241axiom(not(initially(brokenSwitch(device1))),
14242    []).
14243
14244
14245% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4604
14246% HoldsAt(Erratic(Device1),0).
14247axiom(initially(erratic(device1)),
14248    []).
14249
14250
14251% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4605
14252% HoldsAt(PluggedIn(Device1),0).
14253axiom(initially(pluggedIn(device1)),
14254    []).
14255
14256
14257% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4607
14258%; added:
14259
14260
14261% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4608
14262% HoldsAt(DeterminingFluent(Device1),1).
14263holds_at(determiningFluent(device1),1).
14264
14265% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4610
14266% completion Theta Ab1
14267% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4611
14268==> completion(theta).
14269==> completion(ab1).
14270
14271% completion Happens
14272% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4612
14273==> completion(happens).
14274
14275% range time 0 1
14276% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4614
14277==> range(time,0,1).
14278
14279% range offset 1 1
14280% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4615
14281==> range(offset,1,1).
14282%; End of file.
14283%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14284%; FILE: examples/Mueller2006/Chapter12/DefaultEvent.e
14285%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14286%;
14287%; Copyright (c) 2005 IBM Corporation and others.
14288%; All rights reserved. This program and the accompanying materials
14289%; are made available under the terms of the Common Public License v1.0
14290%; which accompanies this distribution, and is available at
14291%; http://www.eclipse.org/legal/cpl-v10.html
14292%;
14293%; Contributors:
14294%; IBM - Initial implementation
14295%;
14296%; @book{Mueller:2006,
14297%;   author = "Erik T. Mueller",
14298%;   year = "2006",
14299%;   title = "Commonsense Reasoning",
14300%;   address = "San Francisco",
14301%;   publisher = "Morgan Kaufmann/Elsevier",
14302%; }
14303%;
14304
14305% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4642
14306% option modeldiff on
14307% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4643
14308:- set_ec_option(modeldiff, on).14309
14310% load foundations/Root.e
14311
14312% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4645
14313% load foundations/EC.e
14314
14315% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4647
14316% sort agent
14317% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4648
14318==> sort(agent).
14319
14320% sort clock
14321% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4649
14322==> sort(clock).
14323
14324% fluent Beeping(clock)
14325 %  fluent(beeping(clock)).
14326% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4651
14327==> mpred_prop(beeping(clock),fluent).
14328==> meta_argtypes(beeping(clock)).
14329
14330% fluent AlarmTime(clock,time)
14331 %  fluent(alarmTime(clock,time)).
14332% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4652
14333==> mpred_prop(alarmTime(clock,time),fluent).
14334==> meta_argtypes(alarmTime(clock,time)).
14335
14336% fluent AlarmOn(clock)
14337 %  fluent(alarmOn(clock)).
14338% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4653
14339==> mpred_prop(alarmOn(clock),fluent).
14340==> meta_argtypes(alarmOn(clock)).
14341
14342% event SetAlarmTime(agent,clock,time)
14343 %  event(setAlarmTime(agent,clock,time)).
14344% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4655
14345==> mpred_prop(setAlarmTime(agent,clock,time),event).
14346==> meta_argtypes(setAlarmTime(agent,clock,time)).
14347
14348% event StartBeeping(clock)
14349 %  event(startBeeping(clock)).
14350% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4656
14351==> mpred_prop(startBeeping(clock),event).
14352==> meta_argtypes(startBeeping(clock)).
14353
14354% event TurnOnAlarm(agent,clock)
14355 %  event(turnOnAlarm(agent,clock)).
14356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4657
14357==> mpred_prop(turnOnAlarm(agent,clock),event).
14358==> meta_argtypes(turnOnAlarm(agent,clock)).
14359
14360% event TurnOffAlarm(agent,clock)
14361 %  event(turnOffAlarm(agent,clock)).
14362% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4658
14363==> mpred_prop(turnOffAlarm(agent,clock),event).
14364==> meta_argtypes(turnOffAlarm(agent,clock)).
14365
14366% predicate Ab1(clock,time)
14367 %  predicate(ab1(clock,time)).
14368% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4660
14369==> mpred_prop(ab1(clock,time),predicate).
14370==> meta_argtypes(ab1(clock,time)).
14371
14372% agent Nathan
14373% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4662
14374==> t(agent,nathan).
14375
14376% clock Clock
14377% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4663
14378==> t(clock,clock).
14379%; Sigma
14380% [agent,clock,time1,time2,time]
14381% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4667
14382% HoldsAt(AlarmTime(clock,time1),time) &
14383% time1!=time2 ->
14384% Initiates(SetAlarmTime(agent,clock,time2),AlarmTime(clock,time2),time).
14385% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4669
14386axiom(initiates(setAlarmTime(Agent, Clock, Time2), alarmTime(Clock, Time2), Time),
14387   
14388    [ holds_at(alarmTime(Clock, Time1), Time),
14389      { dif(Time1, Time2)
14390      }
14391    ]).
14392
14393
14394% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4671
14395% [agent,clock,time1,time2,time]
14396% HoldsAt(AlarmTime(clock,time1),time) &
14397% time1!=time2 ->
14398% Terminates(SetAlarmTime(agent,clock,time2),AlarmTime(clock,time1),time).
14399% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4674
14400axiom(terminates(setAlarmTime(Agent, Clock, Time2), alarmTime(Clock, Time1), Time),
14401   
14402    [ holds_at(alarmTime(Clock, Time1), Time),
14403      { dif(Time1, Time2)
14404      }
14405    ]).
14406
14407
14408% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4676
14409% [agent,clock,time]
14410% Initiates(TurnOnAlarm(agent,clock),AlarmOn(clock),time).
14411% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4677
14412axiom(initiates(turnOnAlarm(Agent, Clock), alarmOn(Clock), Time),
14413    []).
14414
14415
14416% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4679
14417% [agent,clock,time]
14418% Terminates(TurnOffAlarm(agent,clock),AlarmOn(clock),time).
14419% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4680
14420axiom(terminates(turnOffAlarm(Agent, Clock), alarmOn(Clock), Time),
14421    []).
14422
14423
14424% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4682
14425% [clock,time]
14426% Initiates(StartBeeping(clock),Beeping(clock),time).
14427% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4683
14428axiom(initiates(startBeeping(Clock), beeping(Clock), Time),
14429    []).
14430
14431
14432% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4685
14433% [agent,clock,time]
14434% Terminates(TurnOffAlarm(agent,clock),Beeping(clock),time).
14435% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4686
14436axiom(terminates(turnOffAlarm(Agent, Clock), beeping(Clock), Time),
14437    []).
14438
14439
14440% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4688
14441%; Delta
14442% [clock,time]
14443% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4691
14444% HoldsAt(AlarmTime(clock,time),time) &
14445% HoldsAt(AlarmOn(clock),time) &
14446% !Ab1(clock,time) ->
14447% Happens(StartBeeping(clock),time).
14448% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4694
14449axiom(happens(startBeeping(Clock), Time),
14450   
14451    [ holds_at(alarmTime(Clock, Time), Time),
14452      holds_at(alarmOn(Clock), Time),
14453      not(ab1(Clock, Time))
14454    ]).
14455
14456
14457% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4696
14458% Happens(SetAlarmTime(Nathan,Clock,2),0).
14459axiom(happens(setAlarmTime(nathan, clock, 2), t),
14460    [is_time(0)]).
14461
14462
14463% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4697
14464% Happens(TurnOnAlarm(Nathan,Clock),1).
14465axiom(happens(turnOnAlarm(nathan, clock), start),
14466    [is_time(1), b(t, start), ignore(t+1=start)]).
14467
14468
14469% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4699
14470%; Psi
14471% [clock,time1,time2,time]
14472% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4702
14473% HoldsAt(AlarmTime(clock,time1),time) &
14474% HoldsAt(AlarmTime(clock,time2),time) ->
14475% time1=time2.
14476% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4704
14477axiom(Time1=Time2,
14478   
14479    [ holds_at(alarmTime(Clock, Time1), Time),
14480      holds_at(alarmTime(Clock, Time2), Time)
14481    ]).
14482
14483
14484% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4706
14485%; Gamma
14486
14487
14488% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4708
14489% !HoldsAt(AlarmOn(Clock),0).
14490 %  not(initially(alarmOn(clock))).
14491axiom(not(initially(alarmOn(clock))),
14492    []).
14493
14494
14495% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4709
14496% !HoldsAt(Beeping(Clock),0).
14497 %  not(initially(beeping(clock))).
14498axiom(not(initially(beeping(clock))),
14499    []).
14500
14501
14502% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4710
14503% HoldsAt(AlarmTime(Clock,3),0).
14504axiom(initially(alarmTime(clock, 3)),
14505    []).
14506
14507% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4712
14508% completion Happens
14509% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4713
14510==> completion(happens).
14511
14512% completion Theta Ab1
14513% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4714
14514==> completion(theta).
14515==> completion(ab1).
14516
14517% range time 0 3
14518% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4716
14519==> range(time,0,3).
14520
14521% range offset 1 1
14522% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4717
14523==> range(offset,1,1).
14524%; End of file.
14525%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14526%; FILE: examples/Mueller2006/Chapter12/MethodD.e
14527%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14528%;
14529%; Copyright (c) 2005 IBM Corporation and others.
14530%; All rights reserved. This program and the accompanying materials
14531%; are made available under the terms of the Common Public License v1.0
14532%; which accompanies this distribution, and is available at
14533%; http://www.eclipse.org/legal/cpl-v10.html
14534%;
14535%; Contributors:
14536%; IBM - Initial implementation
14537%;
14538%; Method (D)
14539%;
14540%; @book{Mueller:2006,
14541%;   author = "Erik T. Mueller",
14542%;   year = "2006",
14543%;   title = "Commonsense Reasoning",
14544%;   address = "San Francisco",
14545%;   publisher = "Morgan Kaufmann/Elsevier",
14546%; }
14547%;
14548
14549% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4746
14550% load foundations/Root.e
14551
14552% load foundations/EC.e
14553
14554% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4749
14555% sort object
14556% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4750
14557==> sort(object).
14558
14559% object A,B
14560% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4752
14561==> t(object,a).
14562==> t(object,b).
14563
14564% fluent P(object)
14565 %  fluent(p(object)).
14566% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4754
14567==> mpred_prop(p(object),fluent).
14568==> meta_argtypes(p(object)).
14569
14570% fluent Q(object)
14571 %  fluent(q(object)).
14572% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4755
14573==> mpred_prop(q(object),fluent).
14574==> meta_argtypes(q(object)).
14575
14576% fluent R(object)
14577 %  fluent(r(object)).
14578% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4756
14579==> mpred_prop(r(object),fluent).
14580==> meta_argtypes(r(object)).
14581
14582% predicate Ab1(object,time)
14583 %  predicate(ab1(object,time)).
14584% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4758
14585==> mpred_prop(ab1(object,time),predicate).
14586==> meta_argtypes(ab1(object,time)).
14587
14588% predicate Ab2(object,time)
14589 %  predicate(ab2(object,time)).
14590% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4759
14591==> mpred_prop(ab2(object,time),predicate).
14592==> meta_argtypes(ab2(object,time)).
14593
14594
14595% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4760
14596% [object,time]
14597% HoldsAt(P(object),time) & !Ab1(object,time) ->
14598% HoldsAt(Q(object),time).
14599% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4762
14600axiom(holds_at(q(Object), Time),
14601    [holds_at(p(Object), Time), not(ab1(Object, Time))]).
14602
14603
14604% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4764
14605% [object,time]
14606% HoldsAt(R(object),time) & !Ab2(object,time) ->
14607% !HoldsAt(Q(object),time).
14608% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4766
14609axiom(not(holds_at(q(Object), Time)),
14610    [holds_at(r(Object), Time), not(ab2(Object, Time))]).
14611
14612
14613% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4768
14614% [object,time]
14615% HoldsAt(R(object),time) -> HoldsAt(P(object),time).
14616% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4769
14617axiom(holds_at(p(Object), Time),
14618    [holds_at(r(Object), Time)]).
14619
14620
14621% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4771
14622% HoldsAt(R(A),0).
14623axiom(initially(r(a)),
14624    []).
14625
14626
14627% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4772
14628% HoldsAt(P(B),0).
14629axiom(initially(p(b)),
14630    []).
14631
14632
14633% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4773
14634% !HoldsAt(R(B),0).
14635 %  not(initially(r(b))).
14636axiom(not(initially(r(b))),
14637    []).
14638
14639% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4775
14640% Theta: 
14641next_axiom_uses(theta).
14642 
14643
14644
14645% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4776
14646% [object,time]
14647% HoldsAt(R(object),time) -> Ab1(object,time).
14648% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4777
14649axiom(ab1(Object, Time),
14650    [holds_at(r(Object), Time)]).
14651
14652% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4779
14653% range time 0 0
14654% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4780
14655==> range(time,0,0).
14656
14657% range offset 1 1
14658% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4781
14659==> range(offset,1,1).
14660
14661% completion Theta Ab1
14662% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4783
14663==> completion(theta).
14664==> completion(ab1).
14665
14666% completion Theta Ab2
14667% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4784
14668==> completion(theta).
14669==> completion(ab2).
14670%; End of file.
14671%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14672%; FILE: examples/Mueller2006/Chapter12/BrokenDevice.e
14673%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14674%;
14675%; Copyright (c) 2005 IBM Corporation and others.
14676%; All rights reserved. This program and the accompanying materials
14677%; are made available under the terms of the Common Public License v1.0
14678%; which accompanies this distribution, and is available at
14679%; http://www.eclipse.org/legal/cpl-v10.html
14680%;
14681%; Contributors:
14682%; IBM - Initial implementation
14683%;
14684%; @book{Mueller:2006,
14685%;   author = "Erik T. Mueller",
14686%;   year = "2006",
14687%;   title = "Commonsense Reasoning",
14688%;   address = "San Francisco",
14689%;   publisher = "Morgan Kaufmann/Elsevier",
14690%; }
14691%;
14692
14693% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4811
14694% load foundations/Root.e
14695
14696% load foundations/EC.e
14697
14698% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4814
14699% sort agent
14700% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4815
14701==> sort(agent).
14702
14703% sort device
14704% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4816
14705==> sort(device).
14706
14707% agent Nathan
14708% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4818
14709==> t(agent,nathan).
14710
14711% device Device1
14712% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4819
14713==> t(device,device1).
14714
14715% predicate Ab1(device,time)
14716 %  predicate(ab1(device,time)).
14717% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4821
14718==> mpred_prop(ab1(device,time),predicate).
14719==> meta_argtypes(ab1(device,time)).
14720
14721% fluent On(device)
14722 %  fluent(on(device)).
14723% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4823
14724==> mpred_prop(on(device),fluent).
14725==> meta_argtypes(on(device)).
14726
14727% fluent PluggedIn(device)
14728 %  fluent(pluggedIn(device)).
14729% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4824
14730==> mpred_prop(pluggedIn(device),fluent).
14731==> meta_argtypes(pluggedIn(device)).
14732
14733% fluent BrokenSwitch(device)
14734 %  fluent(brokenSwitch(device)).
14735% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4825
14736==> mpred_prop(brokenSwitch(device),fluent).
14737==> meta_argtypes(brokenSwitch(device)).
14738
14739% event TurnOn(agent,device)
14740 %  event(turnOn(agent,device)).
14741% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4827
14742==> mpred_prop(turnOn(agent,device),event).
14743==> meta_argtypes(turnOn(agent,device)).
14744
14745
14746% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4828
14747%; Sigma
14748% [agent,device,time]
14749% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4831
14750% !Ab1(device,time) ->
14751% Initiates(TurnOn(agent,device),On(device),time).
14752% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4832
14753axiom(initiates(turnOn(Agent, Device), on(Device), Time),
14754    [not(ab1(Device, Time))]).
14755
14756
14757% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4834
14758%; Delta
14759
14760
14761% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4836
14762% Happens(TurnOn(Nathan,Device1),0).
14763axiom(happens(turnOn(nathan, device1), t),
14764    [is_time(0)]).
14765
14766
14767% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4838
14768%; Theta
14769
14770% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4840
14771% Theta: 
14772next_axiom_uses(theta).
14773 
14774
14775
14776% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4840
14777% [device,time]
14778 % HoldsAt(BrokenSwitch(device),time) -> Ab1(device,time).
14779axiom(ab1(Device, Time),
14780    [holds_at(brokenSwitch(Device), Time)]).
14781
14782% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4841
14783% Theta: 
14784next_axiom_uses(theta).
14785 
14786
14787
14788% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4841
14789% [device,time]
14790 % !HoldsAt(PluggedIn(device),time) -> Ab1(device,time).
14791axiom(ab1(Device, Time),
14792    [not(holds_at(pluggedIn(Device), Time))]).
14793
14794
14795% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4843
14796%; Gamma
14797
14798
14799% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4845
14800% !HoldsAt(On(Device1),0).
14801 %  not(initially(on(device1))).
14802axiom(not(initially(on(device1))),
14803    []).
14804
14805
14806% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4846
14807% HoldsAt(BrokenSwitch(Device1),0).
14808axiom(initially(brokenSwitch(device1)),
14809    []).
14810
14811
14812% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4848
14813%; added:
14814
14815
14816% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4849
14817% HoldsAt(PluggedIn(Device1),0).
14818axiom(initially(pluggedIn(device1)),
14819    []).
14820
14821
14822% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4851
14823%; entailed:
14824%; !HoldsAt(On(Device1),1).
14825
14826% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4854
14827% completion Theta Ab1
14828% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4855
14829==> completion(theta).
14830==> completion(ab1).
14831
14832% completion Happens
14833% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4856
14834==> completion(happens).
14835
14836% range time 0 1
14837% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4858
14838==> range(time,0,1).
14839
14840% range offset 1 1
14841% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4859
14842==> range(offset,1,1).
14843%; End of file.
14844%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14845%; FILE: examples/Mueller2006/Chapter12/MethodB.e
14846%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14847%;
14848%; Copyright (c) 2005 IBM Corporation and others.
14849%; All rights reserved. This program and the accompanying materials
14850%; are made available under the terms of the Common Public License v1.0
14851%; which accompanies this distribution, and is available at
14852%; http://www.eclipse.org/legal/cpl-v10.html
14853%;
14854%; Contributors:
14855%; IBM - Initial implementation
14856%;
14857%; Method (D)
14858%;
14859%; @book{Mueller:2006,
14860%;   author = "Erik T. Mueller",
14861%;   year = "2006",
14862%;   title = "Commonsense Reasoning",
14863%;   address = "San Francisco",
14864%;   publisher = "Morgan Kaufmann/Elsevier",
14865%; }
14866%;
14867
14868% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4888
14869% load foundations/Root.e
14870
14871% load foundations/EC.e
14872
14873% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4891
14874% sort object
14875% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4892
14876==> sort(object).
14877
14878% object A,B
14879% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4894
14880==> t(object,a).
14881==> t(object,b).
14882
14883% fluent P(object)
14884 %  fluent(p(object)).
14885% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4896
14886==> mpred_prop(p(object),fluent).
14887==> meta_argtypes(p(object)).
14888
14889% fluent Q(object)
14890 %  fluent(q(object)).
14891% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4897
14892==> mpred_prop(q(object),fluent).
14893==> meta_argtypes(q(object)).
14894
14895% predicate Ab(object,time)
14896 %  predicate(ab(object,time)).
14897% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4898
14898==> mpred_prop(ab(object,time),predicate).
14899==> meta_argtypes(ab(object,time)).
14900
14901
14902% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4899
14903% [object,time]
14904% HoldsAt(P(object),time) & !Ab(object,time) ->
14905% HoldsAt(Q(object),time).
14906% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4901
14907axiom(holds_at(q(Object), Time),
14908    [holds_at(p(Object), Time), not(ab(Object, Time))]).
14909
14910
14911% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4903
14912% HoldsAt(P(A),0).
14913axiom(initially(p(a)),
14914    []).
14915
14916
14917% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4904
14918% HoldsAt(P(B),0).
14919axiom(initially(p(b)),
14920    []).
14921
14922% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4906
14923% Theta: 
14924next_axiom_uses(theta).
14925 
14926
14927
14928% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4906
14929% Ab(A,0).
14930ab(a,0).
14931
14932% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4908
14933% range time 0 0
14934% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4909
14935==> range(time,0,0).
14936
14937% range offset 1 1
14938% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4910
14939==> range(offset,1,1).
14940
14941% completion Theta Ab
14942% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4912
14943==> completion(theta).
14944==> completion(ab).
14945%; End of file.
14946%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14947%; FILE: examples/Mueller2006/Chapter13/ModelFinding.e
14948%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
14949%;
14950%; Copyright (c) 2005 IBM Corporation and others.
14951%; All rights reserved. This program and the accompanying materials
14952%; are made available under the terms of the Common Public License v1.0
14953%; which accompanies this distribution, and is available at
14954%; http://www.eclipse.org/legal/cpl-v10.html
14955%;
14956%; Contributors:
14957%; IBM - Initial implementation
14958%;
14959%; @book{Mueller:2006,
14960%;   author = "Erik T. Mueller",
14961%;   year = "2006",
14962%;   title = "Commonsense Reasoning",
14963%;   address = "San Francisco",
14964%;   publisher = "Morgan Kaufmann/Elsevier",
14965%; }
14966%;
14967
14968% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4939
14969% load foundations/Root.e
14970
14971% load foundations/EC.e
14972
14973% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4942
14974% sort agent
14975% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4943
14976==> sort(agent).
14977
14978% fluent Awake(agent)
14979 %  fluent(awake(agent)).
14980% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4945
14981==> mpred_prop(awake(agent),fluent).
14982==> meta_argtypes(awake(agent)).
14983
14984% event WakeUp(agent)
14985 %  event(wakeUp(agent)).
14986% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4946
14987==> mpred_prop(wakeUp(agent),event).
14988==> meta_argtypes(wakeUp(agent)).
14989
14990
14991% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4947
14992% [agent,time]
14993 % Initiates(WakeUp(agent),Awake(agent),time).
14994axiom(initiates(wakeUp(Agent), awake(Agent), Time),
14995    []).
14996
14997
14998% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4948
14999% [agent,time]
15000 % Happens(WakeUp(agent),time) -> !HoldsAt(Awake(agent),time).
15001axiom(requires(wakeUp(Agent), Time),
15002    [not(holds_at(awake(Agent), Time))]).
15003
15004% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4950
15005% agent James
15006% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4951
15007==> t(agent,james).
15008
15009% range time 0 1
15010% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4953
15011==> range(time,0,1).
15012
15013% range offset 1 1
15014% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4954
15015==> range(offset,1,1).
15016%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15017%; FILE: examples/Mueller2006/Chapter13/Postdiction.e
15018%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15019%;
15020%; Copyright (c) 2005 IBM Corporation and others.
15021%; All rights reserved. This program and the accompanying materials
15022%; are made available under the terms of the Common Public License v1.0
15023%; which accompanies this distribution, and is available at
15024%; http://www.eclipse.org/legal/cpl-v10.html
15025%;
15026%; Contributors:
15027%; IBM - Initial implementation
15028%;
15029%; @book{Mueller:2006,
15030%;   author = "Erik T. Mueller",
15031%;   year = "2006",
15032%;   title = "Commonsense Reasoning",
15033%;   address = "San Francisco",
15034%;   publisher = "Morgan Kaufmann/Elsevier",
15035%; }
15036%;
15037
15038% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4979
15039% load foundations/Root.e
15040
15041% load foundations/EC.e
15042
15043% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4982
15044% sort agent
15045% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4983
15046==> sort(agent).
15047
15048% fluent Awake(agent)
15049 %  fluent(awake(agent)).
15050% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4985
15051==> mpred_prop(awake(agent),fluent).
15052==> meta_argtypes(awake(agent)).
15053
15054% event WakeUp(agent)
15055 %  event(wakeUp(agent)).
15056% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4986
15057==> mpred_prop(wakeUp(agent),event).
15058==> meta_argtypes(wakeUp(agent)).
15059
15060
15061% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4987
15062% [agent,time]
15063 % Initiates(WakeUp(agent),Awake(agent),time).
15064axiom(initiates(wakeUp(Agent), awake(Agent), Time),
15065    []).
15066
15067
15068% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4988
15069% [agent,time]
15070 % Happens(WakeUp(agent),time) -> !HoldsAt(Awake(agent),time).
15071axiom(requires(wakeUp(Agent), Time),
15072    [not(holds_at(awake(Agent), Time))]).
15073
15074% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4990
15075% agent James
15076% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4991
15077==> t(agent,james).
15078
15079% Delta: 
15080next_axiom_uses(delta).
15081 
15082
15083
15084% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4991
15085% Happens(WakeUp(James),0).
15086axiom(happens(wakeUp(james), t),
15087    [is_time(0)]).
15088
15089
15090% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4992
15091% HoldsAt(Awake(James),1).
15092holds_at(awake(james),1).
15093
15094% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4994
15095% completion Delta Happens
15096% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4995
15097==> completion(delta).
15098==> completion(happens).
15099
15100% range time 0 1
15101% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4997
15102==> range(time,0,1).
15103
15104% range offset 1 1
15105% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:4998
15106==> range(offset,1,1).
15107%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15108%; FILE: examples/Mueller2006/Chapter13/Deduction2.e
15109%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15110%;
15111%; Copyright (c) 2005 IBM Corporation and others.
15112%; All rights reserved. This program and the accompanying materials
15113%; are made available under the terms of the Common Public License v1.0
15114%; which accompanies this distribution, and is available at
15115%; http://www.eclipse.org/legal/cpl-v10.html
15116%;
15117%; Contributors:
15118%; IBM - Initial implementation
15119%;
15120%; @book{Mueller:2006,
15121%;   author = "Erik T. Mueller",
15122%;   year = "2006",
15123%;   title = "Commonsense Reasoning",
15124%;   address = "San Francisco",
15125%;   publisher = "Morgan Kaufmann/Elsevier",
15126%; }
15127%;
15128
15129% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5023
15130% option timediff off
15131% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5024
15132:- set_ec_option(timediff, off).15133
15134% load foundations/Root.e
15135
15136% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5026
15137% load foundations/EC.e
15138
15139% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5028
15140% sort agent
15141% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5029
15142==> sort(agent).
15143
15144% fluent Awake(agent)
15145 %  fluent(awake(agent)).
15146% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5031
15147==> mpred_prop(awake(agent),fluent).
15148==> meta_argtypes(awake(agent)).
15149
15150% event WakeUp(agent)
15151 %  event(wakeUp(agent)).
15152% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5032
15153==> mpred_prop(wakeUp(agent),event).
15154==> meta_argtypes(wakeUp(agent)).
15155
15156
15157% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5033
15158% [agent,time]
15159 % Initiates(WakeUp(agent),Awake(agent),time).
15160axiom(initiates(wakeUp(Agent), awake(Agent), Time),
15161    []).
15162
15163% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5035
15164% agent James
15165% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5036
15166==> t(agent,james).
15167
15168
15169% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5036
15170% !HoldsAt(Awake(James),0).
15171 %  not(initially(awake(james))).
15172axiom(not(initially(awake(james))),
15173    []).
15174
15175% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5037
15176% Delta: 
15177next_axiom_uses(delta).
15178 
15179
15180
15181% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5037
15182% Happens(WakeUp(James),0).
15183axiom(happens(wakeUp(james), t),
15184    [is_time(0)]).
15185
15186% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5039
15187% completion Delta Happens
15188% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5040
15189==> completion(delta).
15190==> completion(happens).
15191
15192% range time 0 1
15193% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5042
15194==> range(time,0,1).
15195
15196% range offset 1 1
15197% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5043
15198==> range(offset,1,1).
15199%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15200%; FILE: examples/Mueller2006/Chapter13/Deduction1.e
15201%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15202%;
15203%; Copyright (c) 2005 IBM Corporation and others.
15204%; All rights reserved. This program and the accompanying materials
15205%; are made available under the terms of the Common Public License v1.0
15206%; which accompanies this distribution, and is available at
15207%; http://www.eclipse.org/legal/cpl-v10.html
15208%;
15209%; Contributors:
15210%; IBM - Initial implementation
15211%;
15212%; @book{Mueller:2006,
15213%;   author = "Erik T. Mueller",
15214%;   year = "2006",
15215%;   title = "Commonsense Reasoning",
15216%;   address = "San Francisco",
15217%;   publisher = "Morgan Kaufmann/Elsevier",
15218%; }
15219%;
15220
15221% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5068
15222% load foundations/Root.e
15223
15224% load foundations/EC.e
15225
15226% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5071
15227% sort agent
15228% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5072
15229==> sort(agent).
15230
15231% fluent Awake(agent)
15232 %  fluent(awake(agent)).
15233% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5074
15234==> mpred_prop(awake(agent),fluent).
15235==> meta_argtypes(awake(agent)).
15236
15237% event WakeUp(agent)
15238 %  event(wakeUp(agent)).
15239% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5075
15240==> mpred_prop(wakeUp(agent),event).
15241==> meta_argtypes(wakeUp(agent)).
15242
15243
15244% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5076
15245% [agent,time]
15246 % Initiates(WakeUp(agent),Awake(agent),time).
15247axiom(initiates(wakeUp(Agent), awake(Agent), Time),
15248    []).
15249
15250% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5078
15251% agent James
15252% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5079
15253==> t(agent,james).
15254
15255
15256% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5079
15257% !HoldsAt(Awake(James),0).
15258 %  not(initially(awake(james))).
15259axiom(not(initially(awake(james))),
15260    []).
15261
15262% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5080
15263% Delta: 
15264next_axiom_uses(delta).
15265 
15266
15267
15268% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5080
15269% Happens(WakeUp(James),0).
15270axiom(happens(wakeUp(james), t),
15271    [is_time(0)]).
15272
15273% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5082
15274% completion Delta Happens
15275% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5083
15276==> completion(delta).
15277==> completion(happens).
15278
15279% range time 0 1
15280% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5085
15281==> range(time,0,1).
15282
15283% range offset 1 1
15284% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5086
15285==> range(offset,1,1).
15286%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15287%; FILE: examples/Mueller2006/Chapter13/Abduction.e
15288%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15289%;
15290%; Copyright (c) 2005 IBM Corporation and others.
15291%; All rights reserved. This program and the accompanying materials
15292%; are made available under the terms of the Common Public License v1.0
15293%; which accompanies this distribution, and is available at
15294%; http://www.eclipse.org/legal/cpl-v10.html
15295%;
15296%; Contributors:
15297%; IBM - Initial implementation
15298%;
15299%; @book{Mueller:2006,
15300%;   author = "Erik T. Mueller",
15301%;   year = "2006",
15302%;   title = "Commonsense Reasoning",
15303%;   address = "San Francisco",
15304%;   publisher = "Morgan Kaufmann/Elsevier",
15305%; }
15306%;
15307
15308% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5111
15309% load foundations/Root.e
15310
15311% load foundations/EC.e
15312
15313% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5114
15314% sort agent
15315% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5115
15316==> sort(agent).
15317
15318% fluent Awake(agent)
15319 %  fluent(awake(agent)).
15320% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5117
15321==> mpred_prop(awake(agent),fluent).
15322==> meta_argtypes(awake(agent)).
15323
15324% event WakeUp(agent)
15325 %  event(wakeUp(agent)).
15326% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5118
15327==> mpred_prop(wakeUp(agent),event).
15328==> meta_argtypes(wakeUp(agent)).
15329
15330
15331% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5119
15332% [agent,time]
15333 % Initiates(WakeUp(agent),Awake(agent),time).
15334axiom(initiates(wakeUp(Agent), awake(Agent), Time),
15335    []).
15336
15337% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5121
15338% agent James
15339% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5122
15340==> t(agent,james).
15341
15342
15343% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5122
15344% !HoldsAt(Awake(James),0).
15345 %  not(initially(awake(james))).
15346axiom(not(initially(awake(james))),
15347    []).
15348
15349
15350% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5123
15351% HoldsAt(Awake(James),1).
15352holds_at(awake(james),1).
15353
15354% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5125
15355% range time 0 1
15356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5126
15357==> range(time,0,1).
15358
15359% range offset 1 1
15360% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5127
15361==> range(offset,1,1).
15362%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15363%; FILE: examples/Mueller2006/Chapter4/AlarmClock.e
15364%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15365%;
15366%; Copyright (c) 2005 IBM Corporation and others.
15367%; All rights reserved. This program and the accompanying materials
15368%; are made available under the terms of the Common Public License v1.0
15369%; which accompanies this distribution, and is available at
15370%; http://www.eclipse.org/legal/cpl-v10.html
15371%;
15372%; Contributors:
15373%; IBM - Initial implementation
15374%;
15375%; @book{Mueller:2006,
15376%;   author = "Erik T. Mueller",
15377%;   year = "2006",
15378%;   title = "Commonsense Reasoning",
15379%;   address = "San Francisco",
15380%;   publisher = "Morgan Kaufmann/Elsevier",
15381%; }
15382%;
15383
15384% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5152
15385% load foundations/Root.e
15386
15387% load foundations/EC.e
15388
15389% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5155
15390% sort agent
15391% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5156
15392==> sort(agent).
15393
15394% sort clock
15395% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5157
15396==> sort(clock).
15397
15398% fluent Beeping(clock)
15399 %  fluent(beeping(clock)).
15400% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5159
15401==> mpred_prop(beeping(clock),fluent).
15402==> meta_argtypes(beeping(clock)).
15403
15404% fluent AlarmTime(clock,time)
15405 %  fluent(alarmTime(clock,time)).
15406% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5160
15407==> mpred_prop(alarmTime(clock,time),fluent).
15408==> meta_argtypes(alarmTime(clock,time)).
15409
15410% fluent AlarmOn(clock)
15411 %  fluent(alarmOn(clock)).
15412% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5161
15413==> mpred_prop(alarmOn(clock),fluent).
15414==> meta_argtypes(alarmOn(clock)).
15415
15416% event SetAlarmTime(agent,clock,time)
15417 %  event(setAlarmTime(agent,clock,time)).
15418% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5163
15419==> mpred_prop(setAlarmTime(agent,clock,time),event).
15420==> meta_argtypes(setAlarmTime(agent,clock,time)).
15421
15422% event StartBeeping(clock)
15423 %  event(startBeeping(clock)).
15424% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5164
15425==> mpred_prop(startBeeping(clock),event).
15426==> meta_argtypes(startBeeping(clock)).
15427
15428% event TurnOnAlarm(agent,clock)
15429 %  event(turnOnAlarm(agent,clock)).
15430% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5165
15431==> mpred_prop(turnOnAlarm(agent,clock),event).
15432==> meta_argtypes(turnOnAlarm(agent,clock)).
15433
15434% event TurnOffAlarm(agent,clock)
15435 %  event(turnOffAlarm(agent,clock)).
15436% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5166
15437==> mpred_prop(turnOffAlarm(agent,clock),event).
15438==> meta_argtypes(turnOffAlarm(agent,clock)).
15439
15440% agent Nathan
15441% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5168
15442==> t(agent,nathan).
15443
15444% clock Clock
15445% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5169
15446==> t(clock,clock).
15447%; Sigma
15448% [agent,clock,time1,time2,time]
15449% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5173
15450% HoldsAt(AlarmTime(clock,time1),time) &
15451% time1!=time2 ->
15452% Initiates(SetAlarmTime(agent,clock,time2),AlarmTime(clock,time2),time).
15453% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5175
15454axiom(initiates(setAlarmTime(Agent, Clock, Time2), alarmTime(Clock, Time2), Time),
15455   
15456    [ holds_at(alarmTime(Clock, Time1), Time),
15457      { dif(Time1, Time2)
15458      }
15459    ]).
15460
15461
15462% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5177
15463% [agent,clock,time1,time2,time]
15464% HoldsAt(AlarmTime(clock,time1),time) &
15465% time1!=time2 ->
15466% Terminates(SetAlarmTime(agent,clock,time2),AlarmTime(clock,time1),time).
15467% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5180
15468axiom(terminates(setAlarmTime(Agent, Clock, Time2), alarmTime(Clock, Time1), Time),
15469   
15470    [ holds_at(alarmTime(Clock, Time1), Time),
15471      { dif(Time1, Time2)
15472      }
15473    ]).
15474
15475
15476% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5182
15477% [agent,clock,time]
15478% Initiates(TurnOnAlarm(agent,clock),AlarmOn(clock),time).
15479% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5183
15480axiom(initiates(turnOnAlarm(Agent, Clock), alarmOn(Clock), Time),
15481    []).
15482
15483
15484% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5185
15485% [agent,clock,time]
15486% Terminates(TurnOffAlarm(agent,clock),AlarmOn(clock),time).
15487% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5186
15488axiom(terminates(turnOffAlarm(Agent, Clock), alarmOn(Clock), Time),
15489    []).
15490
15491
15492% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5188
15493% [clock,time]
15494% Initiates(StartBeeping(clock),Beeping(clock),time).
15495% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5189
15496axiom(initiates(startBeeping(Clock), beeping(Clock), Time),
15497    []).
15498
15499
15500% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5191
15501% [agent,clock,time]
15502% Terminates(TurnOffAlarm(agent,clock),Beeping(clock),time).
15503% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5192
15504axiom(terminates(turnOffAlarm(Agent, Clock), beeping(Clock), Time),
15505    []).
15506
15507
15508% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5194
15509%; Delta
15510% [clock,time]
15511% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5197
15512% HoldsAt(AlarmTime(clock,time),time) &
15513% HoldsAt(AlarmOn(clock),time) ->
15514% Happens(StartBeeping(clock),time).
15515% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5199
15516axiom(happens(startBeeping(Clock), Time),
15517   
15518    [ holds_at(alarmTime(Clock, Time), Time),
15519      holds_at(alarmOn(Clock), Time)
15520    ]).
15521
15522
15523% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5201
15524% Happens(SetAlarmTime(Nathan,Clock,2),0).
15525axiom(happens(setAlarmTime(nathan, clock, 2), t),
15526    [is_time(0)]).
15527
15528
15529% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5202
15530% Happens(TurnOnAlarm(Nathan,Clock),1).
15531axiom(happens(turnOnAlarm(nathan, clock), start),
15532    [is_time(1), b(t, start), ignore(t+1=start)]).
15533
15534
15535% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5204
15536%; Psi
15537% [clock,time1,time2,time]
15538% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5207
15539% HoldsAt(AlarmTime(clock,time1),time) &
15540% HoldsAt(AlarmTime(clock,time2),time) ->
15541% time1=time2.
15542% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5209
15543axiom(Time1=Time2,
15544   
15545    [ holds_at(alarmTime(Clock, Time1), Time),
15546      holds_at(alarmTime(Clock, Time2), Time)
15547    ]).
15548
15549
15550% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5211
15551%; Gamma
15552
15553
15554% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5213
15555% !HoldsAt(AlarmOn(Clock),0).
15556 %  not(initially(alarmOn(clock))).
15557axiom(not(initially(alarmOn(clock))),
15558    []).
15559
15560
15561% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5214
15562% !HoldsAt(Beeping(Clock),0).
15563 %  not(initially(beeping(clock))).
15564axiom(not(initially(beeping(clock))),
15565    []).
15566
15567
15568% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5215
15569% HoldsAt(AlarmTime(Clock,3),0).
15570axiom(initially(alarmTime(clock, 3)),
15571    []).
15572
15573% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5217
15574% completion Happens
15575% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5218
15576==> completion(happens).
15577
15578% range time 0 3
15579% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5220
15580==> range(time,0,3).
15581
15582% range offset 1 1
15583% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5221
15584==> range(offset,1,1).
15585%; End of file.
15586%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15587%; FILE: examples/Mueller2006/Chapter4/BankAccountServiceFee.e
15588%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15589%;
15590%; Copyright (c) 2005 IBM Corporation and others.
15591%; All rights reserved. This program and the accompanying materials
15592%; are made available under the terms of the Common Public License v1.0
15593%; which accompanies this distribution, and is available at
15594%; http://www.eclipse.org/legal/cpl-v10.html
15595%;
15596%; Contributors:
15597%; IBM - Initial implementation
15598%;
15599%; @book{Mueller:2006,
15600%;   author = "Erik T. Mueller",
15601%;   year = "2006",
15602%;   title = "Commonsense Reasoning",
15603%;   address = "San Francisco",
15604%;   publisher = "Morgan Kaufmann/Elsevier",
15605%; }
15606%;
15607
15608% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5248
15609% option modeldiff on
15610% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5249
15611:- set_ec_option(modeldiff, on).15612
15613% load foundations/Root.e
15614
15615% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5251
15616% load foundations/EC.e
15617
15618% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5253
15619% sort account
15620% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5254
15621==> sort(account).
15622
15623% sort value: integer
15624% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5255
15625==> subsort(value,integer).
15626
15627% account Account1, Account2
15628% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5257
15629==> t(account,account1).
15630==> t(account,account2).
15631
15632% predicate EndOfMonth(time)
15633 %  predicate(endOfMonth(time)).
15634% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5259
15635==> mpred_prop(endOfMonth(time),predicate).
15636==> meta_argtypes(endOfMonth(time)).
15637
15638% function ServiceFee(account): value
15639 %  functional_predicate(serviceFee(account,value)).
15640% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5260
15641==> mpred_prop(serviceFee(account,value),functional_predicate).
15642==> meta_argtypes(serviceFee(account,value)).
15643resultIsa(serviceFee,value).
15644
15645% function MinimumBalance(account): value
15646 %  functional_predicate(minimumBalance(account,value)).
15647% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5261
15648==> mpred_prop(minimumBalance(account,value),functional_predicate).
15649==> meta_argtypes(minimumBalance(account,value)).
15650resultIsa(minimumBalance,value).
15651
15652% fluent ServiceFeeCharged(account)
15653 %  fluent(serviceFeeCharged(account)).
15654% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5263
15655==> mpred_prop(serviceFeeCharged(account),fluent).
15656==> meta_argtypes(serviceFeeCharged(account)).
15657
15658% fluent Balance(account,value)
15659 %  fluent(balance(account,value)).
15660% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5264
15661==> mpred_prop(balance(account,value),fluent).
15662==> meta_argtypes(balance(account,value)).
15663
15664% event Transfer(account,account,value)
15665 %  event(transfer(account,account,value)).
15666% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5266
15667==> mpred_prop(transfer(account,account,value),event).
15668==> meta_argtypes(transfer(account,account,value)).
15669
15670% event MonthlyReset(account)
15671 %  event(monthlyReset(account)).
15672% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5267
15673==> mpred_prop(monthlyReset(account),event).
15674==> meta_argtypes(monthlyReset(account)).
15675
15676% event ChargeServiceFee(account)
15677 %  event(chargeServiceFee(account)).
15678% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5268
15679==> mpred_prop(chargeServiceFee(account),event).
15680==> meta_argtypes(chargeServiceFee(account)).
15681
15682
15683% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5269
15684%; Sigma
15685% [account1,account2,value1,value2,value3,value4,time]
15686% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5272
15687% HoldsAt(Balance(account1,value1),time) &
15688% HoldsAt(Balance(account2,value2),time) &
15689% value3>0 &
15690% value1>=value3 &
15691% value4=(value2+value3) ->
15692% Initiates(Transfer(account1,account2,value3),Balance(account2,value4),time).
15693% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5277
15694axiom(initiates(transfer(Account1, Account2, Value3), balance(Account2, Value4), Time),
15695   
15696    [ holds_at(balance(Account1, Value1), Time),
15697      holds_at(balance(Account2, Value2), Time),
15698      comparison(Value3, 0, >),
15699      Value1>=Value3,
15700      equals(Value4, Value2+Value3)
15701    ]).
15702
15703
15704% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5279
15705% [account1,account2,value1,value2,value3,time]
15706% HoldsAt(Balance(account1,value1),time) &
15707% HoldsAt(Balance(account2,value2),time) &
15708% value3>0 &
15709% value1>=value3 ->
15710% Terminates(Transfer(account1,account2,value3),Balance(account2,value2),time).
15711% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5284
15712axiom(terminates(transfer(Account1, Account2, Value3), balance(Account2, Value2), Time),
15713   
15714    [ holds_at(balance(Account1, Value1), Time),
15715      holds_at(balance(Account2, Value2), Time),
15716      comparison(Value3, 0, >),
15717      Value1>=Value3
15718    ]).
15719
15720
15721% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5286
15722% [account1,account2,value1,value2,value3,value4,time]
15723% HoldsAt(Balance(account1,value1),time) &
15724% HoldsAt(Balance(account2,value2),time) &
15725% value3>0 &
15726% value1>=value3 &
15727% value4=(value1-value3) ->
15728% Initiates(Transfer(account1,account2,value3),Balance(account1,value4),time).
15729% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5292
15730axiom(initiates(transfer(Account1, Account2, Value3), balance(Account1, Value4), Time),
15731   
15732    [ holds_at(balance(Account1, Value1), Time),
15733      holds_at(balance(Account2, Value2), Time),
15734      comparison(Value3, 0, >),
15735      Value1>=Value3,
15736      equals(Value4, Value1-Value3)
15737    ]).
15738
15739
15740% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5294
15741% [account1,account2,value1,value2,value3,time]
15742% HoldsAt(Balance(account1,value1),time) &
15743% HoldsAt(Balance(account2,value2),time) &
15744% value3>0 &
15745% value1>=value3 ->
15746% Terminates(Transfer(account1,account2,value3),Balance(account1,value1),time).
15747% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5299
15748axiom(terminates(transfer(Account1, Account2, Value3), balance(Account1, Value1), Time),
15749   
15750    [ holds_at(balance(Account1, Value1), Time),
15751      holds_at(balance(Account2, Value2), Time),
15752      comparison(Value3, 0, >),
15753      Value1>=Value3
15754    ]).
15755
15756
15757% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5301
15758% [account,time]
15759% Initiates(ChargeServiceFee(account),ServiceFeeCharged(account),time).
15760% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5302
15761axiom(initiates(chargeServiceFee(Account), serviceFeeCharged(Account), Time),
15762    []).
15763
15764
15765% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5304
15766% [account,time]
15767% Terminates(MonthlyReset(account),ServiceFeeCharged(account),time).
15768% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5305
15769axiom(terminates(monthlyReset(Account), serviceFeeCharged(Account), Time),
15770    []).
15771
15772
15773% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5307
15774% [account,value1,value2,time]
15775% HoldsAt(Balance(account,value1),time) &
15776% value2 = (value1-ServiceFee(account)) ->
15777% Initiates(ChargeServiceFee(account),
15778%           Balance(account,value2),
15779%           time).
15780% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5312
15781axiom(initiates(chargeServiceFee(Account), balance(Account, Value2), Time),
15782   
15783    [ holds_at(balance(Account, Value1), Time),
15784      equals(Value2, Value1-serviceFee(Account))
15785    ]).
15786
15787
15788% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5314
15789% [account,value,time]
15790% HoldsAt(Balance(account,value),time) ->
15791% Terminates(ChargeServiceFee(account),Balance(account,value),time).
15792% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5316
15793axiom(terminates(chargeServiceFee(Account), balance(Account, Value), Time),
15794    [holds_at(balance(Account, Value), Time)]).
15795
15796
15797% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5318
15798%; Delta
15799% [account,value,time]
15800% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5321
15801% HoldsAt(Balance(account,value),time) &
15802% value<MinimumBalance(account) &
15803% !HoldsAt(ServiceFeeCharged(account),time) ->
15804% Happens(ChargeServiceFee(account),time).
15805% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5324
15806axiom(happens(chargeServiceFee(Account), Time),
15807   
15808    [ holds_at(balance(Account, Value), Time),
15809      comparison(Value, minimumBalance(Account), <),
15810      not(holds_at(serviceFeeCharged(Account), Time))
15811    ]).
15812
15813
15814% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5326
15815% [account,time]
15816% EndOfMonth(time) ->
15817% Happens(MonthlyReset(account),time).
15818% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5328
15819axiom(happens(monthlyReset(Account), Time),
15820    [endOfMonth(Time)]).
15821
15822
15823% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5330
15824% Happens(Transfer(Account1,Account2,1),0).
15825axiom(happens(transfer(account1, account2, 1), t),
15826    [is_time(0)]).
15827
15828
15829% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5331
15830% Happens(Transfer(Account1,Account2,1),0).
15831axiom(happens(transfer(account1, account2, 1), t),
15832    [is_time(0)]).
15833
15834
15835% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5333
15836%; Psi
15837% [account,value1,value2,time]
15838% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5336
15839% HoldsAt(Balance(account,value1),time) &
15840% HoldsAt(Balance(account,value2),time) ->
15841% value1=value2.
15842% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5338
15843axiom(Value1=Value2,
15844   
15845    [ holds_at(balance(Account, Value1), Time),
15846      holds_at(balance(Account, Value2), Time)
15847    ]).
15848
15849
15850% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5340
15851%; Gamma
15852
15853
15854% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5342
15855% !HoldsAt(ServiceFeeCharged(Account1),0).
15856 %  not(initially(serviceFeeCharged(account1))).
15857axiom(not(initially(serviceFeeCharged(account1))),
15858    []).
15859
15860
15861% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5343
15862% !HoldsAt(ServiceFeeCharged(Account2),0).
15863 %  not(initially(serviceFeeCharged(account2))).
15864axiom(not(initially(serviceFeeCharged(account2))),
15865    []).
15866
15867
15868% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5344
15869% HoldsAt(Balance(Account1,3),0).
15870axiom(initially(balance(account1, 3)),
15871    []).
15872
15873
15874% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5345
15875% HoldsAt(Balance(Account2,1),0).
15876axiom(initially(balance(account2, 1)),
15877    []).
15878
15879
15880% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5346
15881% MinimumBalance(Account1)=3.
15882minimumBalance(account1,3).
15883
15884
15885% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5347
15886% MinimumBalance(Account2)=1.
15887minimumBalance(account2,1).
15888
15889
15890% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5348
15891% ServiceFee(Account1)=1.
15892serviceFee(account1,1).
15893
15894
15895% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5349
15896% ServiceFee(Account2)=1.
15897serviceFee(account2,1).
15898
15899
15900% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5350
15901% [time]
15902 % !EndOfMonth(time).
15903 %  not(endOfMonth(Time)).
15904axiom(not(endOfMonth(EndOfMonth_Ret)),
15905    []).
15906
15907% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5352
15908% completion Happens
15909% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5353
15910==> completion(happens).
15911
15912% range time 0 3
15913% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5355
15914==> range(time,0,3).
15915
15916% range value 1 3
15917% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5356
15918==> range(value,1,3).
15919
15920% range offset 1 1
15921% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5357
15922==> range(offset,1,1).
15923%; End of file.
15924%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15925%; FILE: examples/Mueller2006/Exercises/Counter.e
15926%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
15927%;
15928%; Copyright (c) 2005 IBM Corporation and others.
15929%; All rights reserved. This program and the accompanying materials
15930%; are made available under the terms of the Common Public License v1.0
15931%; which accompanies this distribution, and is available at
15932%; http://www.eclipse.org/legal/cpl-v10.html
15933%;
15934%; Contributors:
15935%; IBM - Initial implementation
15936%;
15937%; @article{DeneckerDupreBelleghem:1998,
15938%;   author = "Marc Denecker and Daniele Theseider Dupr\'{e} and Kristof Van Belleghem",
15939%;   year = "1998",
15940%;   title = "An inductive definition approach to ramifications",
15941%;   journal = "Link{\"{o}}ping Electronic Articles in Computer and Information Science",
15942%;   volume = "3",
15943%;   number = "007",
15944%; }
15945%;
15946%; @book{Mueller:2006,
15947%;   author = "Erik T. Mueller",
15948%;   year = "2006",
15949%;   title = "Commonsense Reasoning",
15950%;   address = "San Francisco",
15951%;   publisher = "Morgan Kaufmann/Elsevier",
15952%; }
15953%;
15954
15955% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5393
15956% load foundations/Root.e
15957
15958% load foundations/EC.e
15959
15960% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5396
15961% sort counter
15962% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5397
15963==> sort(counter).
15964
15965% counter Counter1
15966% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5398
15967==> t(counter,counter1).
15968
15969% event FalseToTrue(counter)
15970 %  event(falseToTrue(counter)).
15971% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5400
15972==> mpred_prop(falseToTrue(counter),event).
15973==> meta_argtypes(falseToTrue(counter)).
15974
15975% event TrueToFalse(counter)
15976 %  event(trueToFalse(counter)).
15977% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5401
15978==> mpred_prop(trueToFalse(counter),event).
15979==> meta_argtypes(trueToFalse(counter)).
15980
15981% fluent Count(counter,integer)
15982 %  fluent(count(counter,integer)).
15983% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5403
15984==> mpred_prop(count(counter,integer),fluent).
15985==> meta_argtypes(count(counter,integer)).
15986
15987% fluent True(counter)
15988 %  fluent(true(counter)).
15989% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5404
15990==> mpred_prop(true(counter),fluent).
15991==> meta_argtypes(true(counter)).
15992
15993% fluent InputLine(counter)
15994 %  fluent(inputLine(counter)).
15995% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5405
15996==> mpred_prop(inputLine(counter),fluent).
15997==> meta_argtypes(inputLine(counter)).
15998
15999% noninertial InputLine
16000% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5406
16001==> noninertial(inputLine).
16002
16003% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5407
16004% Delta: 
16005next_axiom_uses(delta).
16006 
16007
16008
16009% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5407
16010% [counter,time]
16011% !HoldsAt(True(counter),time) &
16012% HoldsAt(InputLine(counter),time) ->
16013% Happens(FalseToTrue(counter),time).
16014% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5410
16015axiom(happens(falseToTrue(Counter), Time),
16016   
16017    [ not(holds_at(true(Counter), Time)),
16018      holds_at(inputLine(Counter), Time)
16019    ]).
16020
16021% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5412
16022% Delta: 
16023next_axiom_uses(delta).
16024 
16025
16026
16027% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5412
16028% [counter,time]
16029% HoldsAt(True(counter),time) &
16030% !HoldsAt(InputLine(counter),time) ->
16031% Happens(TrueToFalse(counter),time).
16032% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5415
16033axiom(happens(trueToFalse(Counter), Time),
16034   
16035    [ holds_at(true(Counter), Time),
16036      not(holds_at(inputLine(Counter), Time))
16037    ]).
16038
16039
16040% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5417
16041% [counter,time]
16042 % Initiates(FalseToTrue(counter),True(counter),time).
16043axiom(initiates(falseToTrue(Counter), true(Counter), Time),
16044    []).
16045
16046
16047% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5419
16048% [counter,time]
16049 % Terminates(TrueToFalse(counter),True(counter),time).
16050axiom(terminates(trueToFalse(Counter), true(Counter), Time),
16051    []).
16052
16053
16054% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5421
16055% [counter,integer1,integer2,time]
16056% HoldsAt(Count(counter,integer1),time) &
16057% (integer2 = (integer1 + 1)) ->
16058% Initiates(FalseToTrue(counter),Count(counter,integer2),time).
16059% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5424
16060axiom(initiates(falseToTrue(Counter), count(Counter, Integer2), Time),
16061   
16062    [ holds_at(count(Counter, Integer1), Time),
16063      equals(Integer2, Integer1+1)
16064    ]).
16065
16066
16067% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5426
16068% [counter,integer,time]
16069% HoldsAt(Count(counter,integer),time) ->
16070% Terminates(FalseToTrue(counter),Count(counter,integer),time).
16071% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5428
16072axiom(terminates(falseToTrue(Counter), count(Counter, Integer), Time),
16073    [holds_at(count(Counter, Integer), Time)]).
16074
16075
16076% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5430
16077% [counter,integer1,integer2,time]
16078% HoldsAt(Count(counter,integer1),time) &
16079% HoldsAt(Count(counter,integer2),time) ->
16080% integer1 = integer2.
16081% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5433
16082axiom(Integer1=Integer2,
16083   
16084    [ holds_at(count(Counter, Integer1), Time),
16085      holds_at(count(Counter, Integer2), Time)
16086    ]).
16087
16088
16089% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5435
16090% !HoldsAt(True(Counter1),0).
16091 %  not(initially(true(counter1))).
16092axiom(not(initially(true(counter1))),
16093    []).
16094
16095
16096% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5436
16097% !HoldsAt(InputLine(Counter1),0).
16098 %  not(initially(inputLine(counter1))).
16099axiom(not(initially(inputLine(counter1))),
16100    []).
16101
16102
16103% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5437
16104% HoldsAt(InputLine(Counter1),1).
16105holds_at(inputLine(counter1),1).
16106
16107
16108% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5438
16109% HoldsAt(InputLine(Counter1),2).
16110holds_at(inputLine(counter1),2).
16111
16112
16113% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5439
16114% HoldsAt(InputLine(Counter1),3).
16115holds_at(inputLine(counter1),3).
16116
16117
16118% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5440
16119% !HoldsAt(InputLine(Counter1),4).
16120 %  not(holds_at(inputLine(counter1),4)).
16121axiom(not(holds_at(inputLine(counter1), t4)),
16122    [b(t, t4), ignore(t+4=t4)]).
16123
16124
16125% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5441
16126% !HoldsAt(InputLine(Counter1),5).
16127 %  not(holds_at(inputLine(counter1),5)).
16128axiom(not(holds_at(inputLine(counter1), t5)),
16129    [b(t, t5), ignore(t+5=t5)]).
16130
16131
16132% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5442
16133% !HoldsAt(InputLine(Counter1),6).
16134 %  not(holds_at(inputLine(counter1),6)).
16135axiom(not(holds_at(inputLine(counter1), t6)),
16136    [b(t, t6), ignore(t+6=t6)]).
16137
16138
16139% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5443
16140% HoldsAt(InputLine(Counter1),7).
16141holds_at(inputLine(counter1),7).
16142
16143
16144% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5444
16145% HoldsAt(InputLine(Counter1),8).
16146holds_at(inputLine(counter1),8).
16147
16148
16149% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5445
16150% HoldsAt(InputLine(Counter1),9).
16151holds_at(inputLine(counter1),9).
16152
16153
16154% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5447
16155% HoldsAt(Count(Counter1,0),0).
16156axiom(initially(count(counter1, 0)),
16157    []).
16158
16159% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5449
16160% completion Happens
16161% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5450
16162==> completion(happens).
16163
16164% range integer 0 6
16165% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5452
16166==> range(integer,0,6).
16167
16168% range time 0 10
16169% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5453
16170==> range(time,0,10).
16171
16172% range offset 1 1
16173% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5454
16174==> range(offset,1,1).
16175%; End of file.
16176%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
16177%; FILE: examples/Mueller2006/Exercises/TeacherTells.e
16178%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
16179%;
16180%; Copyright (c) 2005 IBM Corporation and others.
16181%; All rights reserved. This program and the accompanying materials
16182%; are made available under the terms of the Common Public License v1.0
16183%; which accompanies this distribution, and is available at
16184%; http://www.eclipse.org/legal/cpl-v10.html
16185%;
16186%; Contributors:
16187%; IBM - Initial implementation
16188%;
16189%; @book{Mueller:2006,
16190%;   author = "Erik T. Mueller",
16191%;   year = "2006",
16192%;   title = "Commonsense Reasoning",
16193%;   address = "San Francisco",
16194%;   publisher = "Morgan Kaufmann/Elsevier",
16195%; }
16196%;
16197
16198% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5481
16199% option modeldiff on
16200% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5482
16201:- set_ec_option(modeldiff, on).16202
16203% load foundations/Root.e
16204
16205% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5484
16206% load foundations/EC.e
16207
16208% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5486
16209% sort agent
16210% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5487
16211==> sort(agent).
16212
16213% sort room
16214% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5488
16215==> sort(room).
16216
16217% sort fact
16218% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5489
16219==> sort(fact).
16220
16221% agent Teacher, Student
16222% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5491
16223==> t(agent,teacher).
16224==> t(agent,student).
16225
16226% room Kitchen, Classroom
16227% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5492
16228==> t(room,kitchen).
16229==> t(room,classroom).
16230
16231% fact Fact1, Fact2
16232% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5493
16233==> t(fact,fact1).
16234==> t(fact,fact2).
16235
16236% fluent InRoom(agent,room)
16237 %  fluent(inRoom(agent,room)).
16238% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5495
16239==> mpred_prop(inRoom(agent,room),fluent).
16240==> meta_argtypes(inRoom(agent,room)).
16241
16242% fluent ListeningTo(agent,agent)
16243 %  fluent(listeningTo(agent,agent)).
16244% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5496
16245==> mpred_prop(listeningTo(agent,agent),fluent).
16246==> meta_argtypes(listeningTo(agent,agent)).
16247
16248% fluent Know(agent,fact)
16249 %  fluent(know(agent,fact)).
16250% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5497
16251==> mpred_prop(know(agent,fact),fluent).
16252==> meta_argtypes(know(agent,fact)).
16253
16254% event Tell(agent,agent,fact)
16255 %  event(tell(agent,agent,fact)).
16256% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5499
16257==> mpred_prop(tell(agent,agent,fact),event).
16258==> meta_argtypes(tell(agent,agent,fact)).
16259
16260
16261% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5500
16262%; Sigma
16263% [agent1,agent2,fact,time]
16264% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5503
16265% (
16266% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5503
16267% {room} HoldsAt(InRoom(agent1,room),time) &
16268%         HoldsAt(InRoom(agent2,room),time)) &
16269% HoldsAt(ListeningTo(agent2,agent1),time) ->
16270% Initiates(Tell(agent1,agent2,fact),Know(agent2,fact),time).
16271
16272 /*   exists([Room],
16273             if(((holds_at(inRoom(Agent1, Room), Time), holds_at(inRoom(Agent2, Room), Time)), holds_at(listeningTo(Agent2, Agent1), Time)),
16274                initiates(tell(Agent1, Agent2, Fact),
16275                          know(Agent2, Fact),
16276                          Time))).
16277 */
16278
16279 /*  initiates(tell(Tell_Param, Know_Param, Tell_Ret), know(Know_Param, Tell_Ret), Time6) :-
16280       ( ( holds_at(inRoom(Tell_Param, Some_Param), Time6),
16281           holds_at(inRoom(Know_Param, Some_Param), Time6)
16282         ),
16283         holds_at(listeningTo(Know_Param, Tell_Param), Time6)
16284       ),
16285       some(Some_Param,
16286            '$kolem_Fn_357'(Tell_Param,
16287                            Time6,
16288                            Know_Param,
16289                            Tell_Ret)).
16290 */
16291% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5506
16292axiom(initiates(tell(Tell_Param, Know_Param, Tell_Ret), know(Know_Param, Tell_Ret), Time6),
16293   
16294    [ holds_at(inRoom(Tell_Param, Some_Param), Time6),
16295      holds_at(inRoom(Know_Param, Some_Param), Time6),
16296      holds_at(listeningTo(Know_Param, Tell_Param), Time6),
16297      some(Some_Param,
16298           '$kolem_Fn_357'(Tell_Param,
16299                           Time6,
16300                           Know_Param,
16301                           Tell_Ret))
16302    ]).
16303
16304 /*  not(holds_at(inRoom(InRoom_Param, Some_Param14), Time11)) :-
16305       holds_at(inRoom(InRoom_Param13, Some_Param14), Time11),
16306       holds_at(listeningTo(InRoom_Param13, InRoom_Param),
16307                Time11),
16308       not(initiates(tell(InRoom_Param,
16309                          InRoom_Param13,
16310                          Tell_Ret15),
16311                     know(InRoom_Param13, Tell_Ret15),
16312                     Time11)),
16313       some(Some_Param14,
16314            '$kolem_Fn_357'(InRoom_Param,
16315                            Time11,
16316                            InRoom_Param13,
16317                            Tell_Ret15)).
16318 */
16319axiom(not(holds_at(inRoom(InRoom_Param, Some_Param14), Time11)),
16320   
16321    [ holds_at(inRoom(InRoom_Param13, Some_Param14), Time11),
16322      holds_at(listeningTo(InRoom_Param13, InRoom_Param),
16323               Time11),
16324      not(initiates(tell(InRoom_Param,
16325                         InRoom_Param13,
16326                         Tell_Ret15),
16327                    know(InRoom_Param13, Tell_Ret15),
16328                    Time11)),
16329      some(Some_Param14,
16330           '$kolem_Fn_357'(InRoom_Param,
16331                           Time11,
16332                           InRoom_Param13,
16333                           Tell_Ret15))
16334    ]).
16335
16336 /*  not(holds_at(inRoom(InRoom_Param17, Some_Param19), Time16)) :-
16337       holds_at(inRoom(InRoom_Param18, Some_Param19), Time16),
16338       holds_at(listeningTo(InRoom_Param17, InRoom_Param18),
16339                Time16),
16340       not(initiates(tell(InRoom_Param18,
16341                          InRoom_Param17,
16342                          Tell_Ret20),
16343                     know(InRoom_Param17, Tell_Ret20),
16344                     Time16)),
16345       some(Some_Param19,
16346            '$kolem_Fn_357'(InRoom_Param18,
16347                            Time16,
16348                            InRoom_Param17,
16349                            Tell_Ret20)).
16350 */
16351axiom(not(holds_at(inRoom(InRoom_Param17, Some_Param19), Time16)),
16352   
16353    [ holds_at(inRoom(InRoom_Param18, Some_Param19), Time16),
16354      holds_at(listeningTo(InRoom_Param17, InRoom_Param18),
16355               Time16),
16356      not(initiates(tell(InRoom_Param18,
16357                         InRoom_Param17,
16358                         Tell_Ret20),
16359                    know(InRoom_Param17, Tell_Ret20),
16360                    Time16)),
16361      some(Some_Param19,
16362           '$kolem_Fn_357'(InRoom_Param18,
16363                           Time16,
16364                           InRoom_Param17,
16365                           Tell_Ret20))
16366    ]).
16367
16368 /*  not(holds_at(listeningTo(ListeningTo_Param, InRoom_Param23), Time21)) :-
16369       ( holds_at(inRoom(InRoom_Param23, Some_Param24), Time21),
16370         holds_at(inRoom(ListeningTo_Param, Some_Param24),
16371                  Time21)
16372       ),
16373       not(initiates(tell(InRoom_Param23,
16374                          ListeningTo_Param,
16375                          Tell_Ret25),
16376                     know(ListeningTo_Param, Tell_Ret25),
16377                     Time21)),
16378       some(Some_Param24,
16379            '$kolem_Fn_357'(InRoom_Param23,
16380                            Time21,
16381                            ListeningTo_Param,
16382                            Tell_Ret25)).
16383 */
16384axiom(not(holds_at(listeningTo(ListeningTo_Param, InRoom_Param23), Time21)),
16385   
16386    [ holds_at(inRoom(InRoom_Param23, Some_Param24), Time21),
16387      holds_at(inRoom(ListeningTo_Param, Some_Param24),
16388               Time21),
16389      not(initiates(tell(InRoom_Param23,
16390                         ListeningTo_Param,
16391                         Tell_Ret25),
16392                    know(ListeningTo_Param, Tell_Ret25),
16393                    Time21)),
16394      some(Some_Param24,
16395           '$kolem_Fn_357'(InRoom_Param23,
16396                           Time21,
16397                           ListeningTo_Param,
16398                           Tell_Ret25))
16399    ]).
16400
16401 /*  not(some(Some_Param27, '$kolem_Fn_357'(Fn_357_Param, Time26, Know_Param29, Fn_357_Ret))) :-
16402       not(initiates(tell(Fn_357_Param, Know_Param29, Fn_357_Ret),
16403                     know(Know_Param29, Fn_357_Ret),
16404                     Time26)),
16405       ( holds_at(inRoom(Fn_357_Param, Some_Param27), Time26),
16406         holds_at(inRoom(Know_Param29, Some_Param27), Time26)
16407       ),
16408       holds_at(listeningTo(Know_Param29, Fn_357_Param), Time26).
16409 */
16410axiom(not(some(Some_Param27, '$kolem_Fn_357'(Fn_357_Param, Time26, Know_Param29, Fn_357_Ret))),
16411   
16412    [ not(initiates(tell(Fn_357_Param,
16413                         Know_Param29,
16414                         Fn_357_Ret),
16415                    know(Know_Param29, Fn_357_Ret),
16416                    Time26)),
16417      holds_at(inRoom(Fn_357_Param, Some_Param27), Time26),
16418      holds_at(inRoom(Know_Param29, Some_Param27), Time26),
16419      holds_at(listeningTo(Know_Param29, Fn_357_Param),
16420               Time26)
16421    ]).
16422
16423
16424% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5508
16425%; Delta
16426
16427
16428% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5510
16429% Happens(Tell(Teacher,Student,Fact1),0).
16430axiom(happens(tell(teacher, student, fact1), t),
16431    [is_time(0)]).
16432
16433
16434% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5512
16435%; Psi
16436% [agent,room1,room2,time]
16437% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5515
16438% HoldsAt(InRoom(agent,room1),time) &
16439% HoldsAt(InRoom(agent,room2),time) ->
16440% room1 = room2.
16441% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5517
16442axiom(Room1=Room2,
16443   
16444    [ holds_at(inRoom(Agent, Room1), Time),
16445      holds_at(inRoom(Agent, Room2), Time)
16446    ]).
16447
16448
16449% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5519
16450%; Gamma
16451% [agent,fact]
16452 % !HoldsAt(Know(agent,fact),0).
16453 %  not(initially(know(Agent,Fact))).
16454% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5521
16455axiom(not(initially(know(Know_Param, Know_Ret))),
16456    []).
16457
16458
16459% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5522
16460% [agent1,agent2]
16461 % HoldsAt(ListeningTo(agent1,agent2),0).
16462axiom(initially(listeningTo(Agent1, Agent2)),
16463    []).
16464
16465
16466% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5523
16467% [agent]
16468 % HoldsAt(InRoom(agent,Classroom),0).
16469axiom(initially(inRoom(Agent, classroom)),
16470    []).
16471
16472% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5525
16473% completion Happens
16474% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5526
16475==> completion(happens).
16476
16477% range time 0 1
16478% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5528
16479==> range(time,0,1).
16480
16481% range offset 1 1
16482% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5529
16483==> range(offset,1,1).
16484%; End of file.
16485%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
16486%; FILE: examples/Mueller2006/Exercises/MixingPaints.e
16487%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
16488%;
16489%; Copyright (c) 2005 IBM Corporation and others.
16490%; All rights reserved. This program and the accompanying materials
16491%; are made available under the terms of the Common Public License v1.0
16492%; which accompanies this distribution, and is available at
16493%; http://www.eclipse.org/legal/cpl-v10.html
16494%;
16495%; Contributors:
16496%; IBM - Initial implementation
16497%;
16498%; @book{Mueller:2006,
16499%;   author = "Erik T. Mueller",
16500%;   year = "2006",
16501%;   title = "Commonsense Reasoning",
16502%;   address = "San Francisco",
16503%;   publisher = "Morgan Kaufmann/Elsevier",
16504%; }
16505%;
16506
16507% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5556
16508% load foundations/Root.e
16509
16510% load foundations/EC.e
16511
16512% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5559
16513% sort palette
16514% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5560
16515==> sort(palette).
16516
16517% sort color
16518% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5561
16519==> sort(color).
16520
16521% palette Palette1
16522% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5563
16523==> t(palette,palette1).
16524
16525% color Red, Yellow, Blue, Green
16526% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5564
16527==> t(color,red).
16528==> t(color,yellow).
16529==> t(color,blue).
16530==> t(color,green).
16531
16532% event PlaceOnPalette(palette,color)
16533 %  event(placeOnPalette(palette,color)).
16534% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5566
16535==> mpred_prop(placeOnPalette(palette,color),event).
16536==> meta_argtypes(placeOnPalette(palette,color)).
16537
16538% fluent OnPalette(palette,color)
16539 %  fluent(onPalette(palette,color)).
16540% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5567
16541==> mpred_prop(onPalette(palette,color),fluent).
16542==> meta_argtypes(onPalette(palette,color)).
16543
16544
16545% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5568
16546% [palette,color,time]
16547% !Happens(PlaceOnPalette(palette,Yellow),time) |
16548% !Happens(PlaceOnPalette(palette,Blue),time) ->
16549% Initiates(PlaceOnPalette(palette,color),OnPalette(palette,color),time).
16550% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5571
16551axiom(initiates(placeOnPalette(Palette, Color), onPalette(Palette, Color), Time),
16552    [not(happens(placeOnPalette(Palette, yellow), Time))]).
16553axiom(initiates(placeOnPalette(Palette, Color), onPalette(Palette, Color), Time),
16554    [not(happens(placeOnPalette(Palette, blue), Time))]).
16555
16556
16557% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5573
16558% [palette,color1,color2,time]
16559% Happens(PlaceOnPalette(palette,Yellow),time) &
16560% color1 = Blue &
16561% color2 = Green ->
16562% Initiates(PlaceOnPalette(palette,color1),OnPalette(palette,color2),time).
16563% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5577
16564axiom(initiates(placeOnPalette(Palette, Color1), onPalette(Palette, Color2), Time),
16565   
16566    [ happens(placeOnPalette(Palette, yellow), Time),
16567      equals(Color1, blue),
16568      equals(Color2, green)
16569    ]).
16570
16571
16572% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5579
16573% [palette,color1,color2,time]
16574% !(Happens(PlaceOnPalette(palette,Yellow),time) &
16575%   Happens(PlaceOnPalette(palette,Blue),time)) &
16576% HoldsAt(OnPalette(palette,color1),time) &
16577% color1 != color2 ->
16578% Terminates(PlaceOnPalette(palette,color2),OnPalette(palette,color1),time).
16579% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5584
16580axiom(terminates(placeOnPalette(Palette, Color2), onPalette(Palette, Color1), Time),
16581   
16582    [ not(happens(placeOnPalette(Palette, yellow), Time)),
16583      holds_at(onPalette(Palette, Color1), Time),
16584      { dif(Color1, Color2)
16585      }
16586    ]).
16587axiom(terminates(placeOnPalette(Palette, Color2), onPalette(Palette, Color1), Time),
16588   
16589    [ not(happens(placeOnPalette(Palette, blue), Time)),
16590      holds_at(onPalette(Palette, Color1), Time),
16591      { dif(Color1, Color2)
16592      }
16593    ]).
16594
16595
16596% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5586
16597% [palette,color1,color2,time]
16598% Happens(PlaceOnPalette(palette,Yellow),time) &
16599% HoldsAt(OnPalette(palette,color2),time) &
16600% color1 = Blue &
16601% color2 != Green ->
16602% Terminates(PlaceOnPalette(palette,color1),OnPalette(palette,color2),time).
16603% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5591
16604axiom(terminates(placeOnPalette(Palette, Color1), onPalette(Palette, Color2), Time),
16605   
16606    [ happens(placeOnPalette(Palette, yellow), Time),
16607      holds_at(onPalette(Palette, Color2), Time),
16608      equals(Color1, blue),
16609      { dif(Color2, green)
16610      }
16611    ]).
16612
16613
16614% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5593
16615%; state constraint
16616% [palette,color1,color2,time]
16617% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5596
16618% HoldsAt(OnPalette(palette,color1),time) &
16619% HoldsAt(OnPalette(palette,color2),time) ->
16620% color1 = color2.
16621% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5598
16622axiom(Color1=Color2,
16623   
16624    [ holds_at(onPalette(Palette, Color1), Time),
16625      holds_at(onPalette(Palette, Color2), Time)
16626    ]).
16627
16628
16629% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5600
16630%; (1) place green over red
16631
16632
16633% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5601
16634% HoldsAt(OnPalette(Palette1,Red),0).
16635axiom(initially(onPalette(palette1, red)),
16636    []).
16637
16638% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5602
16639% Delta: 
16640next_axiom_uses(delta).
16641 
16642
16643
16644% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5602
16645% Happens(PlaceOnPalette(Palette1,Green),0).
16646axiom(happens(placeOnPalette(palette1, green), t),
16647    [is_time(0)]).
16648
16649
16650% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5604
16651%; (2) place yellow+blue over green
16652
16653% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5605
16654% Delta: 
16655next_axiom_uses(delta).
16656 
16657
16658
16659% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5605
16660% Happens(PlaceOnPalette(Palette1,Yellow),1).
16661axiom(happens(placeOnPalette(palette1, yellow), start),
16662    [is_time(1), b(t, start), ignore(t+1=start)]).
16663
16664% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5606
16665% Delta: 
16666next_axiom_uses(delta).
16667 
16668
16669
16670% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5606
16671% Happens(PlaceOnPalette(Palette1,Blue),1).
16672axiom(happens(placeOnPalette(palette1, blue), start),
16673    [is_time(1), b(t, start), ignore(t+1=start)]).
16674
16675
16676% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5608
16677%; (3) place yellow
16678
16679% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5609
16680% Delta: 
16681next_axiom_uses(delta).
16682 
16683
16684
16685% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5609
16686% Happens(PlaceOnPalette(Palette1,Yellow),2).
16687axiom(happens(placeOnPalette(palette1, yellow), t2),
16688    [is_time(2), b(t, t2), ignore(t+2=t2)]).
16689
16690
16691% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5611
16692%; (4) place blue
16693
16694% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5612
16695% Delta: 
16696next_axiom_uses(delta).
16697 
16698
16699
16700% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5612
16701% Happens(PlaceOnPalette(Palette1,Blue),3).
16702axiom(happens(placeOnPalette(palette1, blue), t3),
16703    [is_time(3), b(t, t3), ignore(t+3=t3)]).
16704
16705
16706% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5614
16707%; (5) place green
16708
16709% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5615
16710% Delta: 
16711next_axiom_uses(delta).
16712 
16713
16714
16715% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5615
16716% Happens(PlaceOnPalette(Palette1,Yellow),4).
16717axiom(happens(placeOnPalette(palette1, yellow), t4),
16718    [is_time(4), b(t, t4), ignore(t+4=t4)]).
16719
16720% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5616
16721% Delta: 
16722next_axiom_uses(delta).
16723 
16724
16725
16726% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5616
16727% Happens(PlaceOnPalette(Palette1,Blue),4).
16728axiom(happens(placeOnPalette(palette1, blue), t4),
16729    [is_time(4), b(t, t4), ignore(t+4=t4)]).
16730
16731% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5618
16732% completion Delta Happens
16733% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5619
16734==> completion(delta).
16735==> completion(happens).
16736
16737% range time 0 5
16738% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5621
16739==> range(time,0,5).
16740
16741% range offset 1 1
16742% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5622
16743==> range(offset,1,1).
16744%; End of file.
16745%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
16746%; FILE: examples/Mueller2006/Exercises/SnoozeAlarm.e
16747%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
16748%;
16749%; Copyright (c) 2005 IBM Corporation and others.
16750%; All rights reserved. This program and the accompanying materials
16751%; are made available under the terms of the Common Public License v1.0
16752%; which accompanies this distribution, and is available at
16753%; http://www.eclipse.org/legal/cpl-v10.html
16754%;
16755%; Contributors:
16756%; IBM - Initial implementation
16757%;
16758%; Example: Alarm Clock with snooze alarm added
16759%;
16760%; @book{Mueller:2006,
16761%;   author = "Erik T. Mueller",
16762%;   year = "2006",
16763%;   title = "Commonsense Reasoning",
16764%;   address = "San Francisco",
16765%;   publisher = "Morgan Kaufmann/Elsevier",
16766%; }
16767%;
16768
16769% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5651
16770% load foundations/Root.e
16771
16772% load foundations/EC.e
16773
16774% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5654
16775% sort agent
16776% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5655
16777==> sort(agent).
16778
16779% sort clock
16780% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5656
16781==> sort(clock).
16782
16783% fluent Beeping(clock)
16784 %  fluent(beeping(clock)).
16785% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5658
16786==> mpred_prop(beeping(clock),fluent).
16787==> meta_argtypes(beeping(clock)).
16788
16789% fluent AlarmTime(clock,time)
16790 %  fluent(alarmTime(clock,time)).
16791% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5659
16792==> mpred_prop(alarmTime(clock,time),fluent).
16793==> meta_argtypes(alarmTime(clock,time)).
16794
16795% fluent AlarmOn(clock)
16796 %  fluent(alarmOn(clock)).
16797% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5660
16798==> mpred_prop(alarmOn(clock),fluent).
16799==> meta_argtypes(alarmOn(clock)).
16800
16801% event SetAlarmTime(agent,clock,time)
16802 %  event(setAlarmTime(agent,clock,time)).
16803% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5662
16804==> mpred_prop(setAlarmTime(agent,clock,time),event).
16805==> meta_argtypes(setAlarmTime(agent,clock,time)).
16806
16807% event StartBeeping(clock)
16808 %  event(startBeeping(clock)).
16809% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5663
16810==> mpred_prop(startBeeping(clock),event).
16811==> meta_argtypes(startBeeping(clock)).
16812
16813% event TurnOnAlarm(agent,clock)
16814 %  event(turnOnAlarm(agent,clock)).
16815% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5664
16816==> mpred_prop(turnOnAlarm(agent,clock),event).
16817==> meta_argtypes(turnOnAlarm(agent,clock)).
16818
16819% event TurnOffAlarm(agent,clock)
16820 %  event(turnOffAlarm(agent,clock)).
16821% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5665
16822==> mpred_prop(turnOffAlarm(agent,clock),event).
16823==> meta_argtypes(turnOffAlarm(agent,clock)).
16824
16825% event PressSnooze(agent,clock)
16826 %  event(pressSnooze(agent,clock)).
16827% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5667
16828==> mpred_prop(pressSnooze(agent,clock),event).
16829==> meta_argtypes(pressSnooze(agent,clock)).
16830
16831% agent Nathan
16832% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5669
16833==> t(agent,nathan).
16834
16835% clock Clock
16836% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5670
16837==> t(clock,clock).
16838%; Sigma
16839% [agent,clock,time1,time2,time]
16840% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5674
16841% HoldsAt(AlarmTime(clock,time1),time) &
16842% time1!=time2 ->
16843% Initiates(SetAlarmTime(agent,clock,time2),AlarmTime(clock,time2),time).
16844% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5676
16845axiom(initiates(setAlarmTime(Agent, Clock, Time2), alarmTime(Clock, Time2), Time),
16846   
16847    [ holds_at(alarmTime(Clock, Time1), Time),
16848      { dif(Time1, Time2)
16849      }
16850    ]).
16851
16852
16853% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5678
16854% [agent,clock,time1,time2,time]
16855% HoldsAt(AlarmTime(clock,time1),time) &
16856% time1!=time2 ->
16857% Terminates(SetAlarmTime(agent,clock,time2),AlarmTime(clock,time1),time).
16858% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5681
16859axiom(terminates(setAlarmTime(Agent, Clock, Time2), alarmTime(Clock, Time1), Time),
16860   
16861    [ holds_at(alarmTime(Clock, Time1), Time),
16862      { dif(Time1, Time2)
16863      }
16864    ]).
16865
16866
16867% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5683
16868% [agent,clock,time]
16869% Initiates(TurnOnAlarm(agent,clock),AlarmOn(clock),time).
16870% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5684
16871axiom(initiates(turnOnAlarm(Agent, Clock), alarmOn(Clock), Time),
16872    []).
16873
16874
16875% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5686
16876% [agent,clock,time]
16877% Terminates(TurnOffAlarm(agent,clock),AlarmOn(clock),time).
16878% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5687
16879axiom(terminates(turnOffAlarm(Agent, Clock), alarmOn(Clock), Time),
16880    []).
16881
16882
16883% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5689
16884% [clock,time]
16885% Initiates(StartBeeping(clock),Beeping(clock),time).
16886% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5690
16887axiom(initiates(startBeeping(Clock), beeping(Clock), Time),
16888    []).
16889
16890
16891% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5692
16892% [agent,clock,time]
16893% Terminates(TurnOffAlarm(agent,clock),Beeping(clock),time).
16894% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5693
16895axiom(terminates(turnOffAlarm(Agent, Clock), beeping(Clock), Time),
16896    []).
16897
16898
16899% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5695
16900%; added axioms:
16901% [agent,clock,time2,time]
16902% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5698
16903% HoldsAt(Beeping(clock),time) &
16904% time2 = time+9 ->
16905% Initiates(PressSnooze(agent,clock),AlarmTime(clock,time2),time).
16906% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5700
16907axiom(initiates(pressSnooze(Agent, Clock), alarmTime(Clock, Time2), Time),
16908   
16909    [ holds_at(beeping(Clock), Time),
16910      equals(Time2, Time+9)
16911    ]).
16912
16913
16914% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5702
16915% [agent,clock,time1,time2,time]
16916% HoldsAt(Beeping(clock),time) &
16917% HoldsAt(AlarmTime(clock,time1),time) &
16918% time2 = time+9 &
16919% time1 != time2 ->
16920% Terminates(PressSnooze(agent,clock),AlarmTime(clock,time1),time).
16921% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5707
16922axiom(terminates(pressSnooze(Agent, Clock), alarmTime(Clock, Time1), Time),
16923   
16924    [ holds_at(beeping(Clock), Time),
16925      holds_at(alarmTime(Clock, Time1), Time),
16926      equals(Time2, Time+9),
16927      { dif(Time1, Time2)
16928      }
16929    ]).
16930
16931
16932% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5709
16933% [agent,clock,time]
16934% Terminates(PressSnooze(agent,clock),Beeping(clock),time).
16935% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5710
16936axiom(terminates(pressSnooze(Agent, Clock), beeping(Clock), Time),
16937    []).
16938
16939
16940% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5712
16941%; Delta
16942% [clock,time]
16943% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5715
16944% HoldsAt(AlarmTime(clock,time),time) &
16945% HoldsAt(AlarmOn(clock),time) ->
16946% Happens(StartBeeping(clock),time).
16947% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5717
16948axiom(happens(startBeeping(Clock), Time),
16949   
16950    [ holds_at(alarmTime(Clock, Time), Time),
16951      holds_at(alarmOn(Clock), Time)
16952    ]).
16953
16954
16955% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5719
16956% Happens(SetAlarmTime(Nathan,Clock,2),0).
16957axiom(happens(setAlarmTime(nathan, clock, 2), t),
16958    [is_time(0)]).
16959
16960
16961% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5720
16962% Happens(TurnOnAlarm(Nathan,Clock),1).
16963axiom(happens(turnOnAlarm(nathan, clock), start),
16964    [is_time(1), b(t, start), ignore(t+1=start)]).
16965
16966
16967% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5721
16968% Happens(PressSnooze(Nathan,Clock),4).
16969axiom(happens(pressSnooze(nathan, clock), t4),
16970    [is_time(4), b(t, t4), ignore(t+4=t4)]).
16971
16972
16973% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5723
16974%; Psi
16975% [clock,time1,time2,time]
16976% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5726
16977% HoldsAt(AlarmTime(clock,time1),time) &
16978% HoldsAt(AlarmTime(clock,time2),time) ->
16979% time1=time2.
16980% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5728
16981axiom(Time1=Time2,
16982   
16983    [ holds_at(alarmTime(Clock, Time1), Time),
16984      holds_at(alarmTime(Clock, Time2), Time)
16985    ]).
16986
16987
16988% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5730
16989%; Gamma
16990
16991
16992% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5732
16993% !HoldsAt(AlarmOn(Clock),0).
16994 %  not(initially(alarmOn(clock))).
16995axiom(not(initially(alarmOn(clock))),
16996    []).
16997
16998
16999% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5733
17000% !HoldsAt(Beeping(Clock),0).
17001 %  not(initially(beeping(clock))).
17002axiom(not(initially(beeping(clock))),
17003    []).
17004
17005
17006% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5734
17007% HoldsAt(AlarmTime(Clock,3),0).
17008axiom(initially(alarmTime(clock, 3)),
17009    []).
17010
17011% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5736
17012% completion Happens
17013% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5737
17014==> completion(happens).
17015
17016% range time 0 15
17017% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5739
17018==> range(time,0,15).
17019
17020% range offset 1 1
17021% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5740
17022==> range(offset,1,1).
17023%; End of file.
17024%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
17025%; FILE: examples/Mueller2006/Exercises/TelephoneBugs.e
17026%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
17027%;
17028%; Copyright (c) 2005 IBM Corporation and others.
17029%; All rights reserved. This program and the accompanying materials
17030%; are made available under the terms of the Common Public License v1.0
17031%; which accompanies this distribution, and is available at
17032%; http://www.eclipse.org/legal/cpl-v10.html
17033%;
17034%; Contributors:
17035%; IBM - Initial implementation
17036%;
17037%; Example: Telephone
17038%;
17039%; @book{Mueller:2006,
17040%;   author = "Erik T. Mueller",
17041%;   year = "2006",
17042%;   title = "Commonsense Reasoning",
17043%;   address = "San Francisco",
17044%;   publisher = "Morgan Kaufmann/Elsevier",
17045%; }
17046%;
17047
17048% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5769
17049% load foundations/Root.e
17050
17051% load foundations/EC.e
17052
17053% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5772
17054% sort agent
17055% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5773
17056==> sort(agent).
17057
17058% sort phone
17059% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5774
17060==> sort(phone).
17061
17062% agent Agent1, Agent2
17063% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5776
17064==> t(agent,agent1).
17065==> t(agent,agent2).
17066
17067% phone Phone1, Phone2
17068% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5777
17069==> t(phone,phone1).
17070==> t(phone,phone2).
17071
17072% fluent Ringing(phone,phone)
17073 %  fluent(ringing(phone,phone)).
17074% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5779
17075==> mpred_prop(ringing(phone,phone),fluent).
17076==> meta_argtypes(ringing(phone,phone)).
17077
17078% fluent DialTone(phone)
17079 %  fluent(dialTone(phone)).
17080% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5780
17081==> mpred_prop(dialTone(phone),fluent).
17082==> meta_argtypes(dialTone(phone)).
17083
17084% fluent BusySignal(phone)
17085 %  fluent(busySignal(phone)).
17086% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5781
17087==> mpred_prop(busySignal(phone),fluent).
17088==> meta_argtypes(busySignal(phone)).
17089
17090% fluent Idle(phone)
17091 %  fluent(idle(phone)).
17092% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5782
17093==> mpred_prop(idle(phone),fluent).
17094==> meta_argtypes(idle(phone)).
17095
17096% fluent Connected(phone,phone)
17097 %  fluent(connected(phone,phone)).
17098% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5783
17099==> mpred_prop(connected(phone,phone),fluent).
17100==> meta_argtypes(connected(phone,phone)).
17101
17102% fluent Disconnected(phone)
17103 %  fluent(disconnected(phone)).
17104% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5784
17105==> mpred_prop(disconnected(phone),fluent).
17106==> meta_argtypes(disconnected(phone)).
17107
17108% event PickUp(agent,phone)
17109 %  event(pickUp(agent,phone)).
17110% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5786
17111==> mpred_prop(pickUp(agent,phone),event).
17112==> meta_argtypes(pickUp(agent,phone)).
17113
17114% event SetDown(agent,phone)
17115 %  event(setDown(agent,phone)).
17116% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5787
17117==> mpred_prop(setDown(agent,phone),event).
17118==> meta_argtypes(setDown(agent,phone)).
17119
17120% event Dial(agent,phone,phone)
17121 %  event(dial(agent,phone,phone)).
17122% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5788
17123==> mpred_prop(dial(agent,phone,phone),event).
17124==> meta_argtypes(dial(agent,phone,phone)).
17125
17126
17127% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5789
17128%; Sigma
17129% [agent,phone,time]
17130% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5792
17131% HoldsAt(Idle(phone),time) ->
17132% Initiates(PickUp(agent,phone),DialTone(phone),time).
17133% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5793
17134axiom(initiates(pickUp(Agent, Phone), dialTone(Phone), Time),
17135    [holds_at(idle(Phone), Time)]).
17136
17137
17138% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5795
17139% [agent,phone,time]
17140% HoldsAt(Idle(phone),time) ->
17141% Terminates(PickUp(agent,phone),Idle(phone),time).
17142% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5797
17143axiom(terminates(pickUp(Agent, Phone), idle(Phone), Time),
17144    [holds_at(idle(Phone), Time)]).
17145
17146
17147% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5799
17148% [agent,phone,time]
17149% HoldsAt(DialTone(phone),time) ->
17150% Initiates(SetDown(agent,phone),Idle(phone),time).
17151% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5801
17152axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
17153    [holds_at(dialTone(Phone), Time)]).
17154
17155
17156% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5803
17157% [agent,phone,time]
17158% HoldsAt(DialTone(phone),time) ->
17159% Terminates(SetDown(agent,phone),DialTone(phone),time).
17160% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5805
17161axiom(terminates(setDown(Agent, Phone), dialTone(Phone), Time),
17162    [holds_at(dialTone(Phone), Time)]).
17163
17164
17165% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5807
17166% [agent,phone1,phone2,time]
17167% HoldsAt(DialTone(phone1),time) &
17168% HoldsAt(Idle(phone2),time) ->
17169% Initiates(Dial(agent,phone1,phone2),Ringing(phone1,phone2),time).
17170% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5810
17171axiom(initiates(dial(Agent, Phone1, Phone2), ringing(Phone1, Phone2), Time),
17172   
17173    [ holds_at(dialTone(Phone1), Time),
17174      holds_at(idle(Phone2), Time)
17175    ]).
17176
17177
17178% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5812
17179% [agent,phone1,phone2,time]
17180% HoldsAt(DialTone(phone1),time) &
17181% HoldsAt(Idle(phone2),time) ->
17182% Terminates(Dial(agent,phone1,phone2),DialTone(phone1),time).
17183% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5815
17184axiom(terminates(dial(Agent, Phone1, Phone2), dialTone(Phone1), Time),
17185   
17186    [ holds_at(dialTone(Phone1), Time),
17187      holds_at(idle(Phone2), Time)
17188    ]).
17189
17190
17191% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5817
17192% [agent,phone1,phone2,time]
17193% HoldsAt(DialTone(phone1),time) &
17194% HoldsAt(Idle(phone2),time) ->
17195% Terminates(Dial(agent,phone1,phone2),Idle(phone2),time).
17196% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5820
17197axiom(terminates(dial(Agent, Phone1, Phone2), idle(Phone2), Time),
17198   
17199    [ holds_at(dialTone(Phone1), Time),
17200      holds_at(idle(Phone2), Time)
17201    ]).
17202
17203
17204% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5822
17205% [agent,phone1,phone2,time]
17206% HoldsAt(DialTone(phone1),time) &
17207% !HoldsAt(Idle(phone2),time) ->
17208% Initiates(Dial(agent,phone1,phone2),BusySignal(phone1),time).
17209% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5825
17210axiom(initiates(dial(Agent, Phone1, Phone2), busySignal(Phone1), Time),
17211   
17212    [ holds_at(dialTone(Phone1), Time),
17213      not(holds_at(idle(Phone2), Time))
17214    ]).
17215
17216
17217% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5827
17218% [agent,phone1,phone2,time]
17219% HoldsAt(DialTone(phone1),time) &
17220% !HoldsAt(Idle(phone2),time) ->
17221% Terminates(Dial(agent,phone1,phone2),DialTone(phone1),time).
17222% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5830
17223axiom(terminates(dial(Agent, Phone1, Phone2), dialTone(Phone1), Time),
17224   
17225    [ holds_at(dialTone(Phone1), Time),
17226      not(holds_at(idle(Phone2), Time))
17227    ]).
17228
17229
17230% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5832
17231% [agent,phone,time]
17232% HoldsAt(BusySignal(phone),time) ->
17233% Initiates(SetDown(agent,phone),Idle(phone),time).
17234% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5834
17235axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
17236    [holds_at(busySignal(Phone), Time)]).
17237
17238
17239% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5836
17240% [agent,phone,time]
17241% HoldsAt(BusySignal(phone),time) ->
17242% Terminates(SetDown(agent,phone),BusySignal(phone),time).
17243% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5838
17244axiom(terminates(setDown(Agent, Phone), busySignal(Phone), Time),
17245    [holds_at(busySignal(Phone), Time)]).
17246
17247
17248% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5840
17249% [agent,phone1,phone2,time]
17250% HoldsAt(Ringing(phone1,phone2),time) ->
17251% Initiates(SetDown(agent,phone1),Idle(phone1),time).
17252% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5842
17253axiom(initiates(setDown(Agent, Phone1), idle(Phone1), Time),
17254    [holds_at(ringing(Phone1, Phone2), Time)]).
17255
17256
17257% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5844
17258% [agent,phone1,phone2,time]
17259% HoldsAt(Ringing(phone1,phone2),time) ->
17260% Initiates(SetDown(agent,phone1),Idle(phone2),time).
17261% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5846
17262axiom(initiates(setDown(Agent, Phone1), idle(Phone2), Time),
17263    [holds_at(ringing(Phone1, Phone2), Time)]).
17264
17265
17266% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5848
17267% [agent,phone1,phone2,time]
17268% HoldsAt(Ringing(phone1,phone2),time) ->
17269% Terminates(SetDown(agent,phone1),Ringing(phone1,phone2),time).
17270% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5850
17271axiom(terminates(setDown(Agent, Phone1), ringing(Phone1, Phone2), Time),
17272    [holds_at(ringing(Phone1, Phone2), Time)]).
17273
17274
17275% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5852
17276% [agent,phone1,phone2,time]
17277% HoldsAt(Ringing(phone1,phone2),time) ->
17278% Initiates(PickUp(agent,phone2),Connected(phone1,phone2),time).
17279% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5854
17280axiom(initiates(pickUp(Agent, Phone2), connected(Phone1, Phone2), Time),
17281    [holds_at(ringing(Phone1, Phone2), Time)]).
17282
17283
17284% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5856
17285% [agent,phone1,phone2,time]
17286% HoldsAt(Ringing(phone1,phone2),time) ->
17287% Terminates(PickUp(agent,phone2),Ringing(phone1,phone2),time).
17288% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5858
17289axiom(terminates(pickUp(Agent, Phone2), ringing(Phone1, Phone2), Time),
17290    [holds_at(ringing(Phone1, Phone2), Time)]).
17291
17292
17293% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5860
17294% [agent,phone1,phone2,time]
17295% HoldsAt(Connected(phone1,phone2),time) ->
17296% Initiates(SetDown(agent,phone1),Idle(phone1),time).
17297% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5862
17298axiom(initiates(setDown(Agent, Phone1), idle(Phone1), Time),
17299    [holds_at(connected(Phone1, Phone2), Time)]).
17300
17301
17302% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5864
17303% [agent,phone1,phone2,time]
17304% HoldsAt(Connected(phone1,phone2),time) ->
17305% Initiates(SetDown(agent,phone1),Disconnected(phone2),time).
17306% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5866
17307axiom(initiates(setDown(Agent, Phone1), disconnected(Phone2), Time),
17308    [holds_at(connected(Phone1, Phone2), Time)]).
17309
17310
17311% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5868
17312% [agent,phone1,phone2,time]
17313% HoldsAt(Connected(phone1,phone2),time) ->
17314% Terminates(SetDown(agent,phone1),Connected(phone1,phone2),time).
17315% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5870
17316axiom(terminates(setDown(Agent, Phone1), connected(Phone1, Phone2), Time),
17317    [holds_at(connected(Phone1, Phone2), Time)]).
17318
17319
17320% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5872
17321% [agent,phone1,phone2,time]
17322% HoldsAt(Connected(phone1,phone2),time) ->
17323% Initiates(SetDown(agent,phone2),Idle(phone2),time).
17324% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5874
17325axiom(initiates(setDown(Agent, Phone2), idle(Phone2), Time),
17326    [holds_at(connected(Phone1, Phone2), Time)]).
17327
17328
17329% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5876
17330% [agent,phone1,phone2,time]
17331% HoldsAt(Connected(phone1,phone2),time) ->
17332% Initiates(SetDown(agent,phone2),Disconnected(phone1),time).
17333% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5878
17334axiom(initiates(setDown(Agent, Phone2), disconnected(Phone1), Time),
17335    [holds_at(connected(Phone1, Phone2), Time)]).
17336
17337
17338% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5880
17339% [agent,phone1,phone2,time]
17340% HoldsAt(Connected(phone1,phone2),time) ->
17341% Terminates(SetDown(agent,phone2),Connected(phone1,phone2),time).
17342% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5882
17343axiom(terminates(setDown(Agent, Phone2), connected(Phone1, Phone2), Time),
17344    [holds_at(connected(Phone1, Phone2), Time)]).
17345
17346
17347% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5884
17348% [agent,phone,time]
17349% HoldsAt(Disconnected(phone),time) ->
17350% Initiates(SetDown(agent,phone),Idle(phone),time).
17351% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5886
17352axiom(initiates(setDown(Agent, Phone), idle(Phone), Time),
17353    [holds_at(disconnected(Phone), Time)]).
17354
17355
17356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5888
17357% [agent,phone,time]
17358% HoldsAt(Disconnected(phone),time) ->
17359% Terminates(SetDown(agent,phone),Disconnected(phone),time).
17360% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5890
17361axiom(terminates(setDown(Agent, Phone), disconnected(Phone), Time),
17362    [holds_at(disconnected(Phone), Time)]).
17363
17364
17365% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5892
17366%; Delta
17367%; (1) Two agents dial each other simultaneously without first
17368%; picking up phone.
17369
17370
17371% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5896
17372% Happens(Dial(Agent1,Phone1,Phone2),0).
17373axiom(happens(dial(agent1, phone1, phone2), t),
17374    [is_time(0)]).
17375
17376
17377% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5897
17378% Happens(Dial(Agent2,Phone2,Phone1),0).
17379axiom(happens(dial(agent2, phone2, phone1), t),
17380    [is_time(0)]).
17381
17382
17383% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5899
17384%; (2) Two agents dial each other simultaneously.
17385
17386
17387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5900
17388% Happens(PickUp(Agent1,Phone1),1).
17389axiom(happens(pickUp(agent1, phone1), start),
17390    [is_time(1), b(t, start), ignore(t+1=start)]).
17391
17392
17393% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5901
17394% Happens(PickUp(Agent2,Phone2),1).
17395axiom(happens(pickUp(agent2, phone2), start),
17396    [is_time(1), b(t, start), ignore(t+1=start)]).
17397
17398
17399% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5902
17400% Happens(Dial(Agent1,Phone1,Phone2),2).
17401axiom(happens(dial(agent1, phone1, phone2), t2),
17402    [is_time(2), b(t, t2), ignore(t+2=t2)]).
17403
17404
17405% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5903
17406% Happens(Dial(Agent2,Phone2,Phone1),2).
17407axiom(happens(dial(agent2, phone2, phone1), t2),
17408    [is_time(2), b(t, t2), ignore(t+2=t2)]).
17409
17410
17411% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5904
17412% Happens(SetDown(Agent1,Phone1),3).
17413axiom(happens(setDown(agent1, phone1), t3),
17414    [is_time(3), b(t, t3), ignore(t+3=t3)]).
17415
17416
17417% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5905
17418% Happens(SetDown(Agent2,Phone2),3).
17419axiom(happens(setDown(agent2, phone2), t3),
17420    [is_time(3), b(t, t3), ignore(t+3=t3)]).
17421
17422
17423% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5907
17424%; (3) One agent dials another agent just as the other
17425%; agent picks up the phone.
17426
17427
17428% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5909
17429% Happens(PickUp(Agent1,Phone1),4).
17430axiom(happens(pickUp(agent1, phone1), t4),
17431    [is_time(4), b(t, t4), ignore(t+4=t4)]).
17432
17433
17434% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5910
17435% Happens(Dial(Agent1,Phone1,Phone2),5).
17436axiom(happens(dial(agent1, phone1, phone2), t5),
17437    [is_time(5), b(t, t5), ignore(t+5=t5)]).
17438
17439
17440% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5911
17441% Happens(PickUp(Agent2,Phone2),5).
17442axiom(happens(pickUp(agent2, phone2), t5),
17443    [is_time(5), b(t, t5), ignore(t+5=t5)]).
17444
17445
17446% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5913
17447%; Psi
17448% [phone,time]
17449% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5916
17450% !HoldsAt(Ringing(phone,phone),time).
17451 %  not(holds_at(ringing(Phone,Phone),Time)).
17452axiom(not(holds_at(ringing(Ringing_Param, Ringing_Param), Time2)),
17453    []).
17454
17455
17456% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5918
17457% [phone1,phone2,time]
17458% HoldsAt(Ringing(phone1,phone2),time) &
17459% phone1!=phone2 ->
17460% !HoldsAt(Ringing(phone2,phone1),time).
17461% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5921
17462axiom(not(holds_at(ringing(Phone2, Phone1), Time)),
17463   
17464    [ holds_at(ringing(Phone1, Phone2), Time),
17465      dif(Phone1, Phone2)
17466    ]).
17467
17468
17469% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5923
17470% [phone,time]
17471% !HoldsAt(Connected(phone,phone),time).
17472 %  not(holds_at(connected(Phone,Phone),Time)).
17473% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5924
17474axiom(not(holds_at(connected(Connected_Param, Connected_Param), Time2)),
17475    []).
17476
17477
17478% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5926
17479% [phone1,phone2,time]
17480% HoldsAt(Connected(phone1,phone2),time) &
17481% phone1!=phone2 ->
17482% !HoldsAt(Connected(phone2,phone1),time).
17483% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5929
17484axiom(not(holds_at(connected(Phone2, Phone1), Time)),
17485   
17486    [ holds_at(connected(Phone1, Phone2), Time),
17487      dif(Phone1, Phone2)
17488    ]).
17489
17490% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5931
17491% mutex Idle, DialTone, BusySignal, Disconnected
17492% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5932
17493mutex(idle).
17494mutex(dialTone).
17495mutex(busySignal).
17496mutex(disconnected).
17497
17498
17499% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5933
17500% [phone1,phone2,time]
17501% HoldsAt(Idle(phone1),time) ->
17502% !HoldsAt(Ringing(phone1,phone2),time) &
17503% !HoldsAt(Connected(phone1,phone2),time).
17504
17505 /*   if(holds_at(idle(Phone1), Time),
17506          (not(holds_at(ringing(Phone1, Phone2), Time)), not(holds_at(connected(Phone1, Phone2), Time)))).
17507 */
17508
17509 /*  not(holds_at(idle(Ringing_Param), Time3)) :-
17510       (   holds_at(ringing(Ringing_Param, Ringing_Ret), Time3)
17511       ;   holds_at(connected(Ringing_Param, Ringing_Ret), Time3)
17512       ).
17513 */
17514% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5936
17515axiom(not(holds_at(idle(Ringing_Param), Time3)),
17516    [holds_at(ringing(Ringing_Param, Ringing_Ret), Time3)]).
17517axiom(not(holds_at(idle(Ringing_Param), Time3)),
17518    [holds_at(connected(Ringing_Param, Ringing_Ret), Time3)]).
17519
17520 /*  not(holds_at(ringing(Ringing_Param7, Ringing_Ret8), Time6)) :-
17521       holds_at(idle(Ringing_Param7), Time6).
17522 */
17523axiom(not(holds_at(ringing(Ringing_Param7, Ringing_Ret8), Time6)),
17524    [holds_at(idle(Ringing_Param7), Time6)]).
17525
17526 /*  not(holds_at(connected(Connected_Param, Connected_Ret), Time9)) :-
17527       holds_at(idle(Connected_Param), Time9).
17528 */
17529axiom(not(holds_at(connected(Connected_Param, Connected_Ret), Time9)),
17530    [holds_at(idle(Connected_Param), Time9)]).
17531
17532
17533% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5938
17534%; contradicts (3) above:
17535%;[phone1,phone2,time]
17536%;HoldsAt(DialTone(phone2),time) ->
17537%;!HoldsAt(Ringing(phone1,phone2),time) &
17538%;!HoldsAt(Connected(phone1,phone2),time).
17539%; etc.
17540%; Gamma
17541% [phone]
17542 
17543% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5948
17544% HoldsAt(Idle(phone),0).
17545axiom(initially(idle(Phone)),
17546    []).
17547
17548% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5950
17549% completion Happens
17550% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5951
17551==> completion(happens).
17552
17553% range time 0 6
17554% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5953
17555==> range(time,0,6).
17556
17557% range offset 1 1
17558% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5954
17559==> range(offset,1,1).
17560%; End of file.
17561%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
17562%; FILE: examples/Mueller2006/Chapter11/HungryCat.e
17563%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
17564%;
17565%; Copyright (c) 2005 IBM Corporation and others.
17566%; All rights reserved. This program and the accompanying materials
17567%; are made available under the terms of the Common Public License v1.0
17568%; which accompanies this distribution, and is available at
17569%; http://www.eclipse.org/legal/cpl-v10.html
17570%;
17571%; Contributors:
17572%; IBM - Initial implementation
17573%;
17574%; @inproceedings{WinikoffEtAl:2002,
17575%;   author = "Michael Winikoff and Lin Padgham and James Harland and John Thangarajah",
17576%;   year = "2002",
17577%;   title = "Declarative \& procedural goals in intelligent agent systems",
17578%;   editor = "Dieter Fensel and Fausto Giunchiglia and Deborah McGuinness and Mary-Anne Williams",
17579%;   booktitle = "\uppercase{P}roceedings of the \uppercase{E}ighth \uppercase{I}nternational \uppercase{C}onference on \uppercase{P}rinciples of \uppercase{K}nowledge \uppercase{R}epresentation and \uppercase{R}easoning",
17580%;   pages = "470--481",
17581%;   address = "San Francisco",
17582%;   publisher = "Morgan Kaufmann",
17583%; }
17584%;
17585%; @book{Mueller:2006,
17586%;   author = "Erik T. Mueller",
17587%;   year = "2006",
17588%;   title = "Commonsense Reasoning",
17589%;   address = "San Francisco",
17590%;   publisher = "Morgan Kaufmann/Elsevier",
17591%; }
17592%;
17593
17594% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5992
17595% load foundations/Root.e
17596
17597% load foundations/EC.e
17598
17599% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5995
17600% sort object
17601% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5996
17602==> sort(object).
17603
17604% sort agent: object
17605% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5997
17606==> subsort(agent,object).
17607
17608% sort food: object
17609% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5998
17610==> subsort(food,object).
17611
17612% sort surface
17613% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:5999
17614==> sort(surface).
17615
17616% sort plan
17617% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6000
17618==> sort(plan).
17619
17620% reified sort belief
17621 %  reified_sort(belief).
17622% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6002
17623==> mpred_prop(belief,reified_sort).
17624
17625% agent Cat
17626% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6004
17627==> t(agent,cat).
17628
17629% surface Floor, Chair, Shelf, Table
17630% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6005
17631==> t(surface,floor).
17632==> t(surface,chair).
17633==> t(surface,shelf).
17634==> t(surface,table).
17635
17636% food Food1, Food2
17637% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6006
17638==> t(food,food1).
17639==> t(food,food2).
17640
17641% plan P1, P1a, P1b, P2, P2a
17642% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6007
17643==> t(plan,p1).
17644==> t(plan,p1a).
17645==> t(plan,p1b).
17646==> t(plan,p2).
17647==> t(plan,p2a).
17648
17649% predicate SelectedPlan(agent,belief,plan,time)
17650 %  predicate(selectedPlan(agent,belief,plan,time)).
17651% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6009
17652==> mpred_prop(selectedPlan(agent,belief,plan,time),predicate).
17653==> meta_argtypes(selectedPlan(agent,belief,plan,time)).
17654
17655% predicate SoundPlan(agent,belief,plan,time)
17656 %  predicate(soundPlan(agent,belief,plan,time)).
17657% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6010
17658==> mpred_prop(soundPlan(agent,belief,plan,time),predicate).
17659==> meta_argtypes(soundPlan(agent,belief,plan,time)).
17660
17661% fluent On(object,surface)
17662 %  fluent(on(object,surface)).
17663% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6012
17664==> mpred_prop(on(object,surface),fluent).
17665==> meta_argtypes(on(object,surface)).
17666
17667% fluent Goal(agent,belief)
17668 %  fluent(goal(agent,belief)).
17669% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6013
17670==> mpred_prop(goal(agent,belief),fluent).
17671==> meta_argtypes(goal(agent,belief)).
17672
17673% fluent CanJump(surface,surface)
17674 %  fluent(canJump(surface,surface)).
17675% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6014
17676==> mpred_prop(canJump(surface,surface),fluent).
17677==> meta_argtypes(canJump(surface,surface)).
17678
17679% fluent Plan(agent,belief,plan)
17680 %  fluent(plan(agent,belief,plan)).
17681% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6015
17682==> mpred_prop(plan(agent,belief,plan),fluent).
17683==> meta_argtypes(plan(agent,belief,plan)).
17684
17685% fluent Satiated(agent)
17686 %  fluent(satiated(agent)).
17687% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6016
17688==> mpred_prop(satiated(agent),fluent).
17689==> meta_argtypes(satiated(agent)).
17690
17691% fluent Believe(agent,belief)
17692 %  fluent(believe(agent,belief)).
17693% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6017
17694==> mpred_prop(believe(agent,belief),fluent).
17695==> meta_argtypes(believe(agent,belief)).
17696
17697% event AddPlan(agent,belief,plan)
17698 %  event(addPlan(agent,belief,plan)).
17699% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6019
17700==> mpred_prop(addPlan(agent,belief,plan),event).
17701==> meta_argtypes(addPlan(agent,belief,plan)).
17702
17703% event DropPlan(agent,belief,plan)
17704 %  event(dropPlan(agent,belief,plan)).
17705% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6020
17706==> mpred_prop(dropPlan(agent,belief,plan),event).
17707==> meta_argtypes(dropPlan(agent,belief,plan)).
17708
17709% event Jump(agent,surface,surface)
17710 %  event(jump(agent,surface,surface)).
17711% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6021
17712==> mpred_prop(jump(agent,surface,surface),event).
17713==> meta_argtypes(jump(agent,surface,surface)).
17714
17715% event Move(surface,surface,surface)
17716 %  event(move(surface,surface,surface)).
17717% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6022
17718==> mpred_prop(move(surface,surface,surface),event).
17719==> meta_argtypes(move(surface,surface,surface)).
17720
17721% event Eat(agent,food)
17722 %  event(eat(agent,food)).
17723% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6023
17724==> mpred_prop(eat(agent,food),event).
17725==> meta_argtypes(eat(agent,food)).
17726
17727% event Wait(agent)
17728 %  event(wait(agent)).
17729% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6024
17730==> mpred_prop(wait(agent),event).
17731==> meta_argtypes(wait(agent)).
17732
17733% belief BSatiated(agent)
17734% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6026
17735==> t(belief,'bSatiated(agent)').
17736
17737% belief BCanJump(surface,surface)
17738% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6027
17739==> t(belief,'bCanJump(surface').
17740==> t(belief,'surface)').
17741
17742% belief BOn(object,surface)
17743% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6028
17744==> t(belief,'bOn(object').
17745==> t(belief,'surface)').
17746%; Sigma
17747%; A5
17748% [agent,belief,plan,time]
17749% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6033
17750% Initiates(AddPlan(agent,belief,plan),Plan(agent,belief,plan),time).
17751axiom(initiates(addPlan(Agent, Belief, Plan), plan(Agent, Belief, Plan), Time),
17752    []).
17753
17754
17755% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6035
17756%; A6
17757% [agent,belief,plan,time]
17758% Terminates(DropPlan(agent,belief,plan),Plan(agent,belief,plan),time).
17759% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6037
17760axiom(terminates(dropPlan(Agent, Belief, Plan), plan(Agent, Belief, Plan), Time),
17761    []).
17762
17763
17764% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6039
17765% [agent,surface1,surface2,time]
17766% HoldsAt(On(agent,surface1),time) &
17767% HoldsAt(CanJump(surface1,surface2),time) ->
17768% Initiates(Jump(agent,surface1,surface2),On(agent,surface2),time).
17769% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6042
17770axiom(initiates(jump(Agent, Surface1, Surface2), on(Agent, Surface2), Time),
17771   
17772    [ holds_at(on(Agent, Surface1), Time),
17773      holds_at(canJump(Surface1, Surface2), Time)
17774    ]).
17775
17776
17777% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6044
17778% [agent,surface1,surface2,time]
17779% HoldsAt(On(agent,surface1),time) &
17780% HoldsAt(CanJump(surface1,surface2),time) ->
17781% Terminates(Jump(agent,surface1,surface2),On(agent,surface1),time).
17782% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6047
17783axiom(terminates(jump(Agent, Surface1, Surface2), on(Agent, Surface1), Time),
17784   
17785    [ holds_at(on(Agent, Surface1), Time),
17786      holds_at(canJump(Surface1, Surface2), Time)
17787    ]).
17788
17789
17790% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6049
17791% [surface1,surface2,surface3,time]
17792% Initiates(Move(surface1,surface2,surface3),CanJump(surface1,surface3),time).
17793% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6050
17794axiom(initiates(move(Surface1, Surface2, Surface3), canJump(Surface1, Surface3), Time),
17795    []).
17796
17797
17798% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6052
17799% [surface1,surface2,surface3,time]
17800% Terminates(Move(surface1,surface2,surface3),CanJump(surface1,surface2),time).
17801% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6053
17802axiom(terminates(move(Surface1, Surface2, Surface3), canJump(Surface1, Surface2), Time),
17803    []).
17804
17805
17806% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6055
17807% [agent,food,surface,time]
17808% HoldsAt(On(agent,surface),time) &
17809% HoldsAt(On(food,surface),time) ->
17810% Initiates(Eat(agent,food),Satiated(agent),time).
17811% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6058
17812axiom(initiates(eat(Agent, Food), satiated(Agent), Time),
17813   
17814    [ holds_at(on(Agent, Surface), Time),
17815      holds_at(on(Food, Surface), Time)
17816    ]).
17817
17818
17819% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6060
17820% [agent,food,surface,time]
17821% HoldsAt(On(agent,surface),time) &
17822% HoldsAt(On(food,surface),time) ->
17823% Terminates(Eat(agent,food),On(food,surface),time).
17824% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6063
17825axiom(terminates(eat(Agent, Food), on(Food, Surface), Time),
17826   
17827    [ holds_at(on(Agent, Surface), Time),
17828      holds_at(on(Food, Surface), Time)
17829    ]).
17830
17831
17832% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6065
17833% [agent,surface1,surface2,belief,time]
17834% HoldsAt(Believe(agent,BOn(agent,surface1)),time) &
17835% HoldsAt(Believe(agent,BCanJump(surface1,surface2)),time) &
17836% (belief = BOn(agent,surface2)) ->
17837% Initiates(Jump(agent,surface1,surface2),
17838%           Believe(agent,belief),
17839%           time).
17840% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6071
17841axiom(initiates(jump(Agent, Surface1, Surface2), believe(Agent, Belief), Time),
17842   
17843    [ holds_at(believe(Agent, bOn(Agent, Surface1)),
17844               Time),
17845      holds_at(believe(Agent, bCanJump(Surface1, Surface2)),
17846               Time),
17847      equals(Belief, bOn(Agent, Surface2))
17848    ]).
17849
17850
17851% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6073
17852% [agent,surface1,surface2,belief,time]
17853% HoldsAt(Believe(agent,BOn(agent,surface1)),time) &
17854% HoldsAt(Believe(agent,BCanJump(surface1,surface2)),time) &
17855% (belief = BOn(agent,surface1)) ->
17856% Terminates(Jump(agent,surface1,surface2),
17857%            Believe(agent,belief),
17858%            time).
17859% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6079
17860axiom(terminates(jump(Agent, Surface1, Surface2), believe(Agent, Belief), Time),
17861   
17862    [ holds_at(believe(Agent, bOn(Agent, Surface1)),
17863               Time),
17864      holds_at(believe(Agent, bCanJump(Surface1, Surface2)),
17865               Time),
17866      equals(Belief, bOn(Agent, Surface1))
17867    ]).
17868
17869
17870% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6081
17871% [agent,surface1,surface2,surface3,belief,time]
17872% (belief = BCanJump(surface1,surface3)) ->
17873% Initiates(Move(surface1,surface2,surface3),
17874%           Believe(agent,belief),
17875%           time).
17876% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6085
17877axiom(initiates(move(Surface1, Surface2, Surface3), believe(Agent, Belief), Time),
17878    [equals(Belief, bCanJump(Surface1, Surface3))]).
17879
17880
17881% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6087
17882% [agent,surface1,surface2,surface3,belief,time]
17883% (belief = BCanJump(surface1,surface2)) ->
17884% Terminates(Move(surface1,surface2,surface3),
17885%            Believe(agent,belief),
17886%            time).
17887% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6091
17888axiom(terminates(move(Surface1, Surface2, Surface3), believe(Agent, Belief), Time),
17889    [equals(Belief, bCanJump(Surface1, Surface2))]).
17890
17891
17892% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6093
17893% [agent,food,surface,belief,time]
17894% HoldsAt(Believe(agent,BOn(agent,surface)),time) &
17895% HoldsAt(Believe(agent,BOn(food,surface)),time) &
17896% (belief = BSatiated(agent)) ->
17897% Initiates(Eat(agent,food),Believe(agent,belief),time).
17898% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6097
17899axiom(initiates(eat(Agent, Food), believe(Agent, Belief), Time),
17900   
17901    [ holds_at(believe(Agent, bOn(Agent, Surface)), Time),
17902      holds_at(believe(Agent, bOn(Food, Surface)), Time),
17903      equals(Belief, bSatiated(Agent))
17904    ]).
17905
17906
17907% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6099
17908% [agent,food,surface,belief,time]
17909% HoldsAt(Believe(agent,BOn(agent,surface)),time) &
17910% HoldsAt(Believe(agent,BOn(food,surface)),time) &
17911% (belief = BOn(food,surface)) ->
17912% Terminates(Eat(agent,food),Believe(agent,belief),time).
17913% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6103
17914axiom(terminates(eat(Agent, Food), believe(Agent, Belief), Time),
17915   
17916    [ holds_at(believe(Agent, bOn(Agent, Surface)), Time),
17917      holds_at(believe(Agent, bOn(Food, Surface)), Time),
17918      equals(Belief, bOn(Food, Surface))
17919    ]).
17920
17921
17922% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6105
17923%; Delta
17924%; A7
17925% [agent,belief,plan,time]
17926% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6109
17927% HoldsAt(Goal(agent,belief),time) &
17928% !HoldsAt(Believe(agent,belief),time) &
17929% SelectedPlan(agent,belief,plan,time) &
17930% (!{plan1} HoldsAt(Plan(agent,belief,plan1),time)) ->
17931% Happens(AddPlan(agent,belief,plan),time).
17932% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6113
17933axiom(happens(addPlan(Agent, Belief, Plan), Time),
17934   
17935    [ holds_at(goal(Agent, Belief), Time),
17936      not(holds_at(believe(Agent, Belief), Time)),
17937      selectedPlan(Agent, Belief, Plan, Time),
17938      not(holds_at(plan(Agent, Belief, Plan1), Time))
17939    ]).
17940
17941
17942% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6115
17943%; A8
17944% [agent,belief,time]
17945% HoldsAt(Plan(agent,belief,P1),time) &
17946% !HoldsAt(Believe(agent,belief),time) &
17947% SoundPlan(agent,belief,P1,time) ->
17948% Happens(Jump(Cat,Floor,Chair),time).
17949% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6120
17950axiom(happens(jump(cat, floor, chair), Time),
17951   
17952    [ holds_at(plan(Agent, Belief, p1), Time),
17953      not(holds_at(believe(Agent, Belief), Time)),
17954      soundPlan(Agent, Belief, p1, Time)
17955    ]).
17956
17957
17958% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6122
17959% [agent,belief,time]
17960% HoldsAt(Plan(agent,belief,P1a),time) &
17961% !HoldsAt(Believe(agent,belief),time) &
17962% SoundPlan(agent,belief,P1a,time) ->
17963% Happens(Wait(Cat),time).
17964% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6126
17965axiom(happens(wait(cat), Time),
17966   
17967    [ holds_at(plan(Agent, Belief, p1a), Time),
17968      not(holds_at(believe(Agent, Belief), Time)),
17969      soundPlan(Agent, Belief, p1a, Time)
17970    ]).
17971
17972
17973% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6128
17974% [agent,belief,time]
17975% HoldsAt(Plan(agent,belief,P2),time) &
17976% !HoldsAt(Believe(agent,belief),time) &
17977% SoundPlan(agent,belief,P2,time) ->
17978% Happens(Jump(Cat,Chair,Shelf),time).
17979% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6132
17980axiom(happens(jump(cat, chair, shelf), Time),
17981   
17982    [ holds_at(plan(Agent, Belief, p2), Time),
17983      not(holds_at(believe(Agent, Belief), Time)),
17984      soundPlan(Agent, Belief, p2, Time)
17985    ]).
17986
17987
17988% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6134
17989%; A9
17990% [agent,belief,plan,time]
17991% HoldsAt(Plan(agent,belief,plan),time) ->
17992% Happens(DropPlan(agent,belief,plan),time).
17993% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6137
17994axiom(happens(dropPlan(Agent, Belief, Plan), Time),
17995    [holds_at(plan(Agent, Belief, Plan), Time)]).
17996
17997
17998% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6139
17999%; A10
18000% [agent,belief,time]
18001% HoldsAt(Plan(agent,belief,P1),time) &
18002% !HoldsAt(Believe(agent,belief),time) &
18003% SoundPlan(agent,belief,P1,time) ->
18004% Happens(AddPlan(agent,belief,P1a),time).
18005% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6144
18006axiom(happens(addPlan(Agent, Belief, p1a), Time),
18007   
18008    [ holds_at(plan(Agent, Belief, p1), Time),
18009      not(holds_at(believe(Agent, Belief), Time)),
18010      soundPlan(Agent, Belief, p1, Time)
18011    ]).
18012
18013
18014% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6146
18015% [agent,belief,time]
18016% HoldsAt(Plan(agent,belief,P1a),time) &
18017% !HoldsAt(Believe(agent,belief),time) &
18018% SoundPlan(agent,belief,P1a,time) ->
18019% Happens(AddPlan(agent,belief,P1b),time).
18020% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6150
18021axiom(happens(addPlan(Agent, Belief, p1b), Time),
18022   
18023    [ holds_at(plan(Agent, Belief, p1a), Time),
18024      not(holds_at(believe(Agent, Belief), Time)),
18025      soundPlan(Agent, Belief, p1a, Time)
18026    ]).
18027
18028
18029% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6152
18030% [agent,belief,time]
18031% HoldsAt(Plan(agent,belief,P2),time) &
18032% !HoldsAt(Believe(agent,belief),time) &
18033% SoundPlan(agent,belief,P2,time) ->
18034% Happens(AddPlan(agent,belief,P2a),time).
18035% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6156
18036axiom(happens(addPlan(Agent, Belief, p2a), Time),
18037   
18038    [ holds_at(plan(Agent, Belief, p2), Time),
18039      not(holds_at(believe(Agent, Belief), Time)),
18040      soundPlan(Agent, Belief, p2, Time)
18041    ]).
18042
18043
18044% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6158
18045%; reactive behavior
18046% [agent,food,surface,time]
18047% !HoldsAt(Satiated(agent),time) &
18048% HoldsAt(On(agent,surface),time) &
18049% HoldsAt(On(food,surface),time) ->
18050% Happens(Eat(agent,food),time).
18051% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6163
18052axiom(happens(eat(Agent, Food), Time),
18053   
18054    [ not(holds_at(satiated(Agent), Time)),
18055      holds_at(on(Agent, Surface), Time),
18056      holds_at(on(Food, Surface), Time)
18057    ]).
18058
18059
18060% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6165
18061%; narrative
18062
18063
18064% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6167
18065% Happens(Move(Chair,Table,Shelf),2).
18066axiom(happens(move(chair, table, shelf), t2),
18067    [is_time(2), b(t, t2), ignore(t+2=t2)]).
18068
18069
18070% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6169
18071%; SelectedPlan - plan library
18072%;[agent,belief,plan,time]
18073%;SelectedPlan(agent,belief,plan,time) <->
18074%;(agent=Cat & belief=BSatiated(Cat) & plan=P1 & time=0) |
18075%;(agent=Cat & belief=BSatiated(Cat) & plan=P2 & time=4).
18076% [agent,belief,plan,time]
18077% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6177
18078% SelectedPlan(agent,belief,plan,time) <->
18079% ({surface1,surface2,surface3,food}
18080%  HoldsAt(Believe(agent,BOn(agent,surface1)),time) &
18081%  HoldsAt(Believe(agent,BCanJump(surface1,surface2)),time) &
18082%  HoldsAt(Believe(agent,BCanJump(surface2,surface3)),time) &
18083%  HoldsAt(Believe(agent,BOn(food,surface3)),time) &
18084%  belief=BSatiated(agent) &
18085%  plan=P1 &
18086%  time=0) |
18087% ({surface1,surface2,surface3,food}
18088%  HoldsAt(Believe(agent,BOn(agent,surface1)),time) &
18089%  HoldsAt(Believe(agent,BCanJump(surface1,surface2)),time) &
18090%  HoldsAt(Believe(agent,BCanJump(surface2,surface3)),time) &
18091%  HoldsAt(Believe(agent,BOn(food,surface3)),time) &
18092%  belief=BSatiated(agent) &
18093%  plan=P2 &
18094%  time=4).
18095
18096 /*  selectedPlan(Agent, Belief, Plan, Time) <->
18097       (   exists([Surface1, Surface2, Surface3, Food],
18098                   (holds_at(believe(Agent, bOn(Agent, Surface1)), Time), holds_at(believe(Agent, bCanJump(Surface1, Surface2)), Time), holds_at(believe(Agent, bCanJump(Surface2, Surface3)), Time), holds_at(believe(Agent, bOn(Food, Surface3)), Time), Belief=bSatiated(Agent), Plan=p1, Time=0))
18099       ;   exists([Surface18, Surface29, Surface310, Food11],
18100                   (holds_at(believe(Agent, bOn(Agent, Surface18)), Time), holds_at(believe(Agent, bCanJump(Surface18, Surface29)), Time), holds_at(believe(Agent, bCanJump(Surface29, Surface310)), Time), holds_at(believe(Agent, bOn(Food11, Surface310)), Time), Belief=bSatiated(Agent), Plan=p2, Time=4))
18101       ).
18102 */
18103% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6193
18104axiom(selectedPlan(Agent, Belief, Plan, Time),
18105   
18106    [ holds_at(believe(Agent, bOn(Agent, Surface1)),
18107               Time),
18108      holds_at(believe(Agent, bCanJump(Surface1, Surface2)),
18109               Time),
18110      holds_at(believe(Agent, bCanJump(Surface2, Surface3)),
18111               Time),
18112      holds_at(believe(Agent, bOn(Food, Surface3)), Time),
18113      equals(Belief, bSatiated(Agent)),
18114      equals(Plan, p1),
18115      equals(Time, 0)
18116    ]).
18117axiom(selectedPlan(Agent, Belief, Plan, Time),
18118   
18119    [ holds_at(believe(Agent, bOn(Agent, Surface18)),
18120               Time),
18121      holds_at(believe(Agent, bCanJump(Surface18, Surface29)),
18122               Time),
18123      holds_at(believe(Agent, bCanJump(Surface29, Surface310)),
18124               Time),
18125      holds_at(believe(Agent, bOn(Food11, Surface310)),
18126               Time),
18127      equals(Belief, bSatiated(Agent)),
18128      equals(Plan, p2),
18129      equals(Time, 4)
18130    ]).
18131
18132 /*   if(selectedPlan(Agent, Belief, Plan, Time),
18133          (exists([Surface1, Surface2, Surface3, Food],  (holds_at(believe(Agent, bOn(Agent, Surface1)), Time), holds_at(believe(Agent, bCanJump(Surface1, Surface2)), Time), holds_at(believe(Agent, bCanJump(Surface2, Surface3)), Time), holds_at(believe(Agent, bOn(Food, Surface3)), Time), Belief=bSatiated(Agent), Plan=p1, Time=0));exists([Surface18, Surface29, Surface310, Food11],  (holds_at(believe(Agent, bOn(Agent, Surface18)), Time), holds_at(believe(Agent, bCanJump(Surface18, Surface29)), Time), holds_at(believe(Agent, bCanJump(Surface29, Surface310)), Time), holds_at(believe(Agent, bOn(Food11, Surface310)), Time), Belief=bSatiated(Agent), Plan=p2, Time=4)))).
18134 */
18135todo_later(if(selectedPlan(Agent, Belief, Plan, Time),  (exists([Surface1, Surface2, Surface3, Food],  (holds_at(believe(Agent, bOn(Agent, Surface1)), Time), holds_at(believe(Agent, bCanJump(Surface1, Surface2)), Time), holds_at(believe(Agent, bCanJump(Surface2, Surface3)), Time), holds_at(believe(Agent, bOn(Food, Surface3)), Time), Belief=bSatiated(Agent), Plan=p1, Time=0));exists([Surface18, Surface29, Surface310, Food11],  (holds_at(believe(Agent, bOn(Agent, Surface18)), Time), holds_at(believe(Agent, bCanJump(Surface18, Surface29)), Time), holds_at(believe(Agent, bCanJump(Surface29, Surface310)), Time), holds_at(believe(Agent, bOn(Food11, Surface310)), Time), Belief=bSatiated(Agent), Plan=p2, Time=4)))), [(not(selectedPlan(SelectedPlan_Param, Equals_Param, Equals_Param32, Time12)):-(not(holds_at(believe(SelectedPlan_Param, bOn(SelectedPlan_Param, BCanJump_Param)), Time12));not(holds_at(believe(SelectedPlan_Param, bCanJump(BCanJump_Param, BCanJump_Param29)), Time12));not(holds_at(believe(SelectedPlan_Param, bCanJump(BCanJump_Param29, BCanJump_Ret)), Time12));not(holds_at(believe(SelectedPlan_Param, bOn(BOn_Param, BCanJump_Ret)), Time12));not(equals(Equals_Param, bSatiated(SelectedPlan_Param)));not(equals(Equals_Param32, p1));not(equals(Time12, 0))), (not(holds_at(believe(SelectedPlan_Param, bOn(SelectedPlan_Param, BCanJump_Param33)), Time12));not(holds_at(believe(SelectedPlan_Param, bCanJump(BCanJump_Param33, BCanJump_Param34)), Time12));not(holds_at(believe(SelectedPlan_Param, bCanJump(BCanJump_Param34, BCanJump_Ret127)), Time12));not(holds_at(believe(SelectedPlan_Param, bOn(BOn_Param35, BCanJump_Ret127)), Time12));not(equals(Equals_Param, bSatiated(SelectedPlan_Param)));not(equals(Equals_Param32, p2));not(equals(Time12, 4)))),  (holds_at(believe(Believe_Param, bOn(Believe_Param, BOn_Ret)), Time13):-(not(holds_at(believe(Believe_Param, bOn(Believe_Param, BCanJump_Param37)), Time13));not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param37, BCanJump_Param38)), Time13));not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param38, BCanJump_Ret129)), Time13));not(holds_at(believe(Believe_Param, bOn(BOn_Param39, BCanJump_Ret129)), Time13));not(equals(Equals_Param40, bSatiated(Believe_Param)));not(equals(Equals_Param41, p2));not(equals(Time13, 4))), selectedPlan(Believe_Param, Equals_Param40, Equals_Param41, Time13)),  (holds_at(believe(Believe_Param42, bCanJump(BCanJump_Param43, BCanJump_Ret130)), Time14):-(not(holds_at(believe(Believe_Param42, bOn(Believe_Param42, BCanJump_Param44)), Time14));not(holds_at(believe(Believe_Param42, bCanJump(BCanJump_Param44, BCanJump_Param45)), Time14));not(holds_at(believe(Believe_Param42, bCanJump(BCanJump_Param45, BCanJump_Ret131)), Time14));not(holds_at(believe(Believe_Param42, bOn(BOn_Param46, BCanJump_Ret131)), Time14));not(equals(Equals_Param47, bSatiated(Believe_Param42)));not(equals(Equals_Param48, p2));not(equals(Time14, 4))), selectedPlan(Believe_Param42, Equals_Param47, Equals_Param48, Time14)),  (holds_at(believe(Believe_Param49, bCanJump(BCanJump_Param50, BCanJump_Ret132)), Time15):-(not(holds_at(believe(Believe_Param49, bOn(Believe_Param49, BCanJump_Param51)), Time15));not(holds_at(believe(Believe_Param49, bCanJump(BCanJump_Param51, BCanJump_Param52)), Time15));not(holds_at(believe(Believe_Param49, bCanJump(BCanJump_Param52, BCanJump_Ret133)), Time15));not(holds_at(believe(Believe_Param49, bOn(BOn_Param53, BCanJump_Ret133)), Time15));not(equals(Equals_Param54, bSatiated(Believe_Param49)));not(equals(Equals_Param55, p2));not(equals(Time15, 4))), selectedPlan(Believe_Param49, Equals_Param54, Equals_Param55, Time15)),  (holds_at(believe(Believe_Param56, bOn(BOn_Param57, BOn_Ret134)), Time16):-(not(holds_at(believe(Believe_Param56, bOn(Believe_Param56, BCanJump_Param58)), Time16));not(holds_at(believe(Believe_Param56, bCanJump(BCanJump_Param58, BCanJump_Param59)), Time16));not(holds_at(believe(Believe_Param56, bCanJump(BCanJump_Param59, BCanJump_Ret135)), Time16));not(holds_at(believe(Believe_Param56, bOn(BOn_Param60, BCanJump_Ret135)), Time16));not(equals(Equals_Param61, bSatiated(Believe_Param56)));not(equals(Equals_Param62, p2));not(equals(Time16, 4))), selectedPlan(Believe_Param56, Equals_Param61, Equals_Param62, Time16)),  (equals(Equals_Param63, bSatiated(Believe_Param64)):-(not(holds_at(believe(Believe_Param64, bOn(Believe_Param64, BCanJump_Param65)), Time17));not(holds_at(believe(Believe_Param64, bCanJump(BCanJump_Param65, BCanJump_Param66)), Time17));not(holds_at(believe(Believe_Param64, bCanJump(BCanJump_Param66, BCanJump_Ret136)), Time17));not(holds_at(believe(Believe_Param64, bOn(BOn_Param67, BCanJump_Ret136)), Time17));not(equals(Equals_Param63, bSatiated(Believe_Param64)));not(equals(Equals_Param68, p2));not(equals(Time17, 4))), selectedPlan(Believe_Param64, Equals_Param63, Equals_Param68, Time17)),  (equals(Equals_Param69, p1):-(not(holds_at(believe(Believe_Param70, bOn(Believe_Param70, BCanJump_Param71)), Time18));not(holds_at(believe(Believe_Param70, bCanJump(BCanJump_Param71, BCanJump_Param72)), Time18));not(holds_at(believe(Believe_Param70, bCanJump(BCanJump_Param72, BCanJump_Ret137)), Time18));not(holds_at(believe(Believe_Param70, bOn(BOn_Param73, BCanJump_Ret137)), Time18));not(equals(Equals_Param74, bSatiated(Believe_Param70)));not(equals(Equals_Param69, p2));not(equals(Time18, 4))), selectedPlan(Believe_Param70, Equals_Param74, Equals_Param69, Time18)),  (equals(Time19, 0):-(not(holds_at(believe(Believe_Param75, bOn(Believe_Param75, BCanJump_Param76)), Time19));not(holds_at(believe(Believe_Param75, bCanJump(BCanJump_Param76, BCanJump_Param77)), Time19));not(holds_at(believe(Believe_Param75, bCanJump(BCanJump_Param77, BCanJump_Ret138)), Time19));not(holds_at(believe(Believe_Param75, bOn(BOn_Param78, BCanJump_Ret138)), Time19));not(equals(Equals_Param79, bSatiated(Believe_Param75)));not(equals(Equals_Param80, p2));not(equals(Time19, 4))), selectedPlan(Believe_Param75, Equals_Param79, Equals_Param80, Time19)),  (holds_at(believe(Believe_Param81, bOn(Believe_Param81, BOn_Ret139)), Time20):-(not(holds_at(believe(Believe_Param81, bOn(Believe_Param81, BCanJump_Param82)), Time20));not(holds_at(believe(Believe_Param81, bCanJump(BCanJump_Param82, BCanJump_Param83)), Time20));not(holds_at(believe(Believe_Param81, bCanJump(BCanJump_Param83, BCanJump_Ret140)), Time20));not(holds_at(believe(Believe_Param81, bOn(BOn_Param84, BCanJump_Ret140)), Time20));not(equals(Equals_Param85, bSatiated(Believe_Param81)));not(equals(Equals_Param86, p1));not(equals(Time20, 0))), selectedPlan(Believe_Param81, Equals_Param85, Equals_Param86, Time20)),  (holds_at(believe(Believe_Param87, bCanJump(BCanJump_Param88, BCanJump_Ret141)), Time21):-(not(holds_at(believe(Believe_Param87, bOn(Believe_Param87, BCanJump_Param89)), Time21));not(holds_at(believe(Believe_Param87, bCanJump(BCanJump_Param89, BCanJump_Param90)), Time21));not(holds_at(believe(Believe_Param87, bCanJump(BCanJump_Param90, BCanJump_Ret142)), Time21));not(holds_at(believe(Believe_Param87, bOn(BOn_Param91, BCanJump_Ret142)), Time21));not(equals(Equals_Param92, bSatiated(Believe_Param87)));not(equals(Equals_Param93, p1));not(equals(Time21, 0))), selectedPlan(Believe_Param87, Equals_Param92, Equals_Param93, Time21)),  (holds_at(believe(Believe_Param94, bCanJump(BCanJump_Param95, BCanJump_Ret143)), Time22):-(not(holds_at(believe(Believe_Param94, bOn(Believe_Param94, BCanJump_Param96)), Time22));not(holds_at(believe(Believe_Param94, bCanJump(BCanJump_Param96, BCanJump_Param97)), Time22));not(holds_at(believe(Believe_Param94, bCanJump(BCanJump_Param97, BCanJump_Ret144)), Time22));not(holds_at(believe(Believe_Param94, bOn(BOn_Param98, BCanJump_Ret144)), Time22));not(equals(Equals_Param99, bSatiated(Believe_Param94)));not(equals(Equals_Param100, p1));not(equals(Time22, 0))), selectedPlan(Believe_Param94, Equals_Param99, Equals_Param100, Time22)),  (holds_at(believe(Believe_Param101, bOn(BOn_Param102, BOn_Ret145)), Time23):-(not(holds_at(believe(Believe_Param101, bOn(Believe_Param101, BCanJump_Param103)), Time23));not(holds_at(believe(Believe_Param101, bCanJump(BCanJump_Param103, BCanJump_Param104)), Time23));not(holds_at(believe(Believe_Param101, bCanJump(BCanJump_Param104, BCanJump_Ret146)), Time23));not(holds_at(believe(Believe_Param101, bOn(BOn_Param105, BCanJump_Ret146)), Time23));not(equals(Equals_Param106, bSatiated(Believe_Param101)));not(equals(Equals_Param107, p1));not(equals(Time23, 0))), selectedPlan(Believe_Param101, Equals_Param106, Equals_Param107, Time23)),  (equals(Equals_Param108, bSatiated(Believe_Param109)):-(not(holds_at(believe(Believe_Param109, bOn(Believe_Param109, BCanJump_Param110)), Time24));not(holds_at(believe(Believe_Param109, bCanJump(BCanJump_Param110, BCanJump_Param111)), Time24));not(holds_at(believe(Believe_Param109, bCanJump(BCanJump_Param111, BCanJump_Ret147)), Time24));not(holds_at(believe(Believe_Param109, bOn(BOn_Param112, BCanJump_Ret147)), Time24));not(equals(Equals_Param108, bSatiated(Believe_Param109)));not(equals(Equals_Param113, p1));not(equals(Time24, 0))), selectedPlan(Believe_Param109, Equals_Param108, Equals_Param113, Time24)),  (equals(Equals_Param114, p2):-(not(holds_at(believe(Believe_Param115, bOn(Believe_Param115, BCanJump_Param116)), Time25));not(holds_at(believe(Believe_Param115, bCanJump(BCanJump_Param116, BCanJump_Param117)), Time25));not(holds_at(believe(Believe_Param115, bCanJump(BCanJump_Param117, BCanJump_Ret148)), Time25));not(holds_at(believe(Believe_Param115, bOn(BOn_Param118, BCanJump_Ret148)), Time25));not(equals(Equals_Param119, bSatiated(Believe_Param115)));not(equals(Equals_Param114, p1));not(equals(Time25, 0))), selectedPlan(Believe_Param115, Equals_Param119, Equals_Param114, Time25)),  (equals(Time26, 4):-(not(holds_at(believe(Believe_Param120, bOn(Believe_Param120, BCanJump_Param121)), Time26));not(holds_at(believe(Believe_Param120, bCanJump(BCanJump_Param121, BCanJump_Param122)), Time26));not(holds_at(believe(Believe_Param120, bCanJump(BCanJump_Param122, BCanJump_Ret149)), Time26));not(holds_at(believe(Believe_Param120, bOn(BOn_Param123, BCanJump_Ret149)), Time26));not(equals(Equals_Param124, bSatiated(Believe_Param120)));not(equals(Equals_Param125, p1));not(equals(Time26, 0))), selectedPlan(Believe_Param120, Equals_Param124, Equals_Param125, Time26))], 15==15).
18136
18137
18138% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6196
18139%; SoundPlan
18140% [agent,belief,plan,time]
18141% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6199
18142% SoundPlan(agent,belief,plan,time) <->
18143% (plan=P1 ->
18144%  HoldsAt(Believe(agent,BCanJump(Floor,Chair)),time) &
18145%  HoldsAt(Believe(agent,BCanJump(Chair,Table)),time)) &
18146% ((plan=P1a | plan=P1b) ->
18147%   HoldsAt(Believe(agent,BCanJump(Chair,Table)),time)).
18148
18149 /*  soundPlan(Agent, Belief, Plan, Time) <->
18150       if(Plan=p1,
18151           (holds_at(believe(Agent, bCanJump(floor, chair)), Time), holds_at(believe(Agent, bCanJump(chair, table)), Time))),
18152       if((Plan=p1a;Plan=p1b),
18153          holds_at(believe(Agent, bCanJump(chair, table)), Time)).
18154 */
18155% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6204
18156axiom(soundPlan(Agent, Belief, Plan, Time),
18157   
18158    [ holds_at(believe(Agent, bCanJump(floor, chair)), Time),
18159      holds_at(believe(Agent, bCanJump(chair, table)), Time),
18160      holds_at(believe(Agent, bCanJump(chair, table)), Time)
18161    ]).
18162axiom(soundPlan(Agent, Belief, Plan, Time),
18163   
18164    [ holds_at(believe(Agent, bCanJump(floor, chair)), Time),
18165      holds_at(believe(Agent, bCanJump(chair, table)), Time),
18166      not(equals(Plan, p1a)),
18167      not(equals(Plan, p1b))
18168    ]).
18169axiom(soundPlan(Agent, Belief, Plan, Time),
18170   
18171    [ holds_at(believe(Agent, bCanJump(chair, table)), Time),
18172      not(equals(Plan, p1))
18173    ]).
18174axiom(soundPlan(Agent, Belief, Plan, Time),
18175   
18176    [ not(equals(Plan, p1a)),
18177      not(equals(Plan, p1b)),
18178      not(equals(Plan, p1))
18179    ]).
18180
18181 /*   if(soundPlan(Agent, Belief, Plan, Time),
18182          (if(Plan=p1,  (holds_at(believe(Agent, bCanJump(floor, chair)), Time), holds_at(believe(Agent, bCanJump(chair, table)), Time))), if((Plan=p1a;Plan=p1b), holds_at(believe(Agent, bCanJump(chair, table)), Time)))).
18183 */
18184
18185 /*  not(soundPlan(SoundPlan_Param, _, Equals_Param, Time4)) :-
18186       (   equals(Equals_Param, p1),
18187           (   not(holds_at(believe(SoundPlan_Param, bCanJump(floor, chair)),
18188                            Time4))
18189           ;   not(holds_at(believe(SoundPlan_Param, bCanJump(chair, table)),
18190                            Time4))
18191           )
18192       ;   not(holds_at(believe(SoundPlan_Param, bCanJump(chair, table)),
18193                        Time4)),
18194           (   equals(Equals_Param, p1a)
18195           ;   equals(Equals_Param, p1b)
18196           )
18197       ).
18198 */
18199axiom(not(soundPlan(SoundPlan_Param, _, Equals_Param, Time4)),
18200   
18201    [ not(holds_at(believe(SoundPlan_Param, bCanJump(floor, chair)),
18202                   Time4)),
18203      equals(Equals_Param, p1)
18204    ]).
18205axiom(not(soundPlan(SoundPlan_Param, _, Equals_Param, Time4)),
18206   
18207    [ not(holds_at(believe(SoundPlan_Param, bCanJump(chair, table)),
18208                   Time4)),
18209      equals(Equals_Param, p1)
18210    ]).
18211axiom(not(soundPlan(SoundPlan_Param, _, Equals_Param, Time4)),
18212   
18213    [ equals(Equals_Param, p1a),
18214      not(holds_at(believe(SoundPlan_Param, bCanJump(chair, table)),
18215                   Time4))
18216    ]).
18217axiom(not(soundPlan(SoundPlan_Param, _, Equals_Param, Time4)),
18218   
18219    [ equals(Equals_Param, p1b),
18220      not(holds_at(believe(SoundPlan_Param, bCanJump(chair, table)),
18221                   Time4))
18222    ]).
18223
18224 /*  not(equals(Equals_Param8, p1)) :-
18225       (   not(holds_at(believe(Believe_Param, bCanJump(floor, chair)),
18226                        Time7))
18227       ;   not(holds_at(believe(Believe_Param, bCanJump(chair, table)),
18228                        Time7))
18229       ),
18230       soundPlan(Believe_Param, _, Equals_Param8, Time7).
18231 */
18232axiom(not(equals(Equals_Param8, p1)),
18233   
18234    [ not(holds_at(believe(Believe_Param, bCanJump(floor, chair)),
18235                   Time7)),
18236      soundPlan(Believe_Param, _, Equals_Param8, Time7)
18237    ]).
18238axiom(not(equals(Equals_Param8, p1)),
18239   
18240    [ not(holds_at(believe(Believe_Param, bCanJump(chair, table)),
18241                   Time7)),
18242      soundPlan(Believe_Param, _, Equals_Param8, Time7)
18243    ]).
18244
18245 /*  holds_at(believe(Believe_Param11, bCanJump(floor, chair)), Time10) :-
18246       equals(Equals_Param12, p1),
18247       soundPlan(Believe_Param11, _, Equals_Param12, Time10).
18248 */
18249axiom(holds_at(believe(Believe_Param11, bCanJump(floor, chair)), Time10),
18250   
18251    [ equals(Equals_Param12, p1),
18252      soundPlan(Believe_Param11,
18253                _,
18254                Equals_Param12,
18255                Time10)
18256    ]).
18257
18258 /*  holds_at(believe(Believe_Param14, bCanJump(chair, table)), Time13) :-
18259       equals(Equals_Param15, p1),
18260       soundPlan(Believe_Param14, _, Equals_Param15, Time13).
18261 */
18262axiom(holds_at(believe(Believe_Param14, bCanJump(chair, table)), Time13),
18263   
18264    [ equals(Equals_Param15, p1),
18265      soundPlan(Believe_Param14,
18266                _,
18267                Equals_Param15,
18268                Time13)
18269    ]).
18270
18271 /*  holds_at(believe(Believe_Param17, bCanJump(chair, table)), Time16) :-
18272       (   equals(Equals_Param18, p1a)
18273       ;   equals(Equals_Param18, p1b)
18274       ),
18275       soundPlan(Believe_Param17, _, Equals_Param18, Time16).
18276 */
18277axiom(holds_at(believe(Believe_Param17, bCanJump(chair, table)), Time16),
18278   
18279    [ equals(Equals_Param18, p1a),
18280      soundPlan(Believe_Param17,
18281                _,
18282                Equals_Param18,
18283                Time16)
18284    ]).
18285axiom(holds_at(believe(Believe_Param17, bCanJump(chair, table)), Time16),
18286   
18287    [ equals(Equals_Param18, p1b),
18288      soundPlan(Believe_Param17,
18289                _,
18290                Equals_Param18,
18291                Time16)
18292    ]).
18293
18294 /*  not(equals(Equals_Param20, p1a)) :-
18295       not(holds_at(believe(Believe_Param21, bCanJump(chair, table)),
18296                    Time19)),
18297       soundPlan(Believe_Param21, _, Equals_Param20, Time19).
18298 */
18299axiom(not(equals(Equals_Param20, p1a)),
18300   
18301    [ not(holds_at(believe(Believe_Param21, bCanJump(chair, table)),
18302                   Time19)),
18303      soundPlan(Believe_Param21,
18304                _,
18305                Equals_Param20,
18306                Time19)
18307    ]).
18308
18309 /*  not(equals(Equals_Param23, p1b)) :-
18310       not(holds_at(believe(Believe_Param24, bCanJump(chair, table)),
18311                    Time22)),
18312       soundPlan(Believe_Param24, _, Equals_Param23, Time22).
18313 */
18314axiom(not(equals(Equals_Param23, p1b)),
18315   
18316    [ not(holds_at(believe(Believe_Param24, bCanJump(chair, table)),
18317                   Time22)),
18318      soundPlan(Believe_Param24,
18319                _,
18320                Equals_Param23,
18321                Time22)
18322    ]).
18323
18324
18325% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6206
18326%; Gamma
18327% [agent,belief]
18328% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6209
18329% HoldsAt(Goal(agent,belief),0) <->
18330% (agent=Cat & belief=BSatiated(Cat)).
18331
18332 /*  holds_at(goal(Agent, Belief), 0) <->
18333       Agent=cat,
18334       Belief=bSatiated(cat).
18335 */
18336% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6210
18337axiom(holds_at(goal(Agent, Belief), t),
18338    [equals(Agent, cat), equals(Belief, bSatiated(cat))]).
18339
18340 /*   if(holds_at(goal(Agent, Belief), 0),
18341          (Agent=cat, Belief=bSatiated(cat))).
18342 */
18343
18344 /*  not(holds_at(goal(Goal_Param, Equals_Param), 0)) :-
18345       (   not(equals(Goal_Param, cat))
18346       ;   not(equals(Equals_Param, bSatiated(cat)))
18347       ).
18348 */
18349axiom(not(holds_at(goal(Goal_Param, Equals_Param), t)),
18350    [not(equals(Goal_Param, cat))]).
18351axiom(not(holds_at(goal(Goal_Param, Equals_Param), t)),
18352    [not(equals(Equals_Param, bSatiated(cat)))]).
18353
18354 /*  equals(Equals_Param4, cat) :-
18355       holds_at(goal(Equals_Param4, Goal_Ret), 0).
18356 */
18357axiom(equals(Equals_Param4, cat),
18358    [holds_at(goal(Equals_Param4, Goal_Ret), t)]).
18359
18360 /*  equals(Equals_Param6, bSatiated(cat)) :-
18361       holds_at(goal(Goal_Param7, Equals_Param6), 0).
18362 */
18363axiom(equals(Equals_Param6, bSatiated(cat)),
18364    [holds_at(goal(Goal_Param7, Equals_Param6), t)]).
18365
18366
18367% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6212
18368% [agent,belief,plan]
18369 % !HoldsAt(Plan(agent,belief,plan),0).
18370 %  not(initially(plan(Agent,Belief,Plan))).
18371axiom(not(initially(plan(Plan_Param, _, Plan_Ret))),
18372    []).
18373
18374
18375% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6214
18376% [object,surface]
18377 % HoldsAt(On(object,surface),0) <->
18378% (object=Cat & surface=Floor) |
18379% (object=Food1 & surface=Table) |
18380% (object=Food2 & surface=Shelf).
18381
18382 /*  holds_at(on(Object, Surface), 0) <->
18383       (   Object=cat,
18384           Surface=floor
18385       ;   Object=food1,
18386           Surface=(table)
18387       ;   Object=food2,
18388           Surface=shelf
18389       ).
18390 */
18391% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6217
18392axiom(holds_at(on(Object, Surface), t),
18393    [equals(Object, cat), equals(Surface, floor)]).
18394axiom(holds_at(on(Object, Surface), t),
18395    [equals(Object, food1), equals(Surface, table)]).
18396axiom(holds_at(on(Object, Surface), t),
18397    [equals(Object, food2), equals(Surface, shelf)]).
18398
18399 /*   if(holds_at(on(Object, Surface), 0),
18400          (Object=cat, Surface=floor;Object=food1, Surface=(table);Object=food2, Surface=shelf)).
18401 */
18402
18403 /*  not(holds_at(on(On_Param, Equals_Param), 0)) :-
18404       (   not(equals(On_Param, cat))
18405       ;   not(equals(Equals_Param, floor))
18406       ),
18407       (   not(equals(On_Param, food1))
18408       ;   not(equals(Equals_Param, table))
18409       ),
18410       (   not(equals(On_Param, food2))
18411       ;   not(equals(Equals_Param, shelf))
18412       ).
18413 */
18414axiom(not(holds_at(on(On_Param, Equals_Param), t)),
18415   
18416    [ not(equals(On_Param, food2)),
18417      not(equals(On_Param, food1)),
18418      not(equals(On_Param, cat))
18419    ]).
18420axiom(not(holds_at(on(On_Param, Equals_Param), t)),
18421   
18422    [ not(equals(Equals_Param, shelf)),
18423      not(equals(On_Param, food1)),
18424      not(equals(On_Param, cat))
18425    ]).
18426axiom(not(holds_at(on(On_Param, Equals_Param), t)),
18427   
18428    [ not(equals(On_Param, food2)),
18429      not(equals(Equals_Param, table)),
18430      not(equals(On_Param, cat))
18431    ]).
18432axiom(not(holds_at(on(On_Param, Equals_Param), t)),
18433   
18434    [ not(equals(Equals_Param, shelf)),
18435      not(equals(Equals_Param, table)),
18436      not(equals(On_Param, cat))
18437    ]).
18438axiom(not(holds_at(on(On_Param, Equals_Param), t)),
18439   
18440    [ not(equals(On_Param, food2)),
18441      not(equals(On_Param, food1)),
18442      not(equals(Equals_Param, floor))
18443    ]).
18444axiom(not(holds_at(on(On_Param, Equals_Param), t)),
18445   
18446    [ not(equals(Equals_Param, shelf)),
18447      not(equals(On_Param, food1)),
18448      not(equals(Equals_Param, floor))
18449    ]).
18450axiom(not(holds_at(on(On_Param, Equals_Param), t)),
18451   
18452    [ not(equals(On_Param, food2)),
18453      not(equals(Equals_Param, table)),
18454      not(equals(Equals_Param, floor))
18455    ]).
18456axiom(not(holds_at(on(On_Param, Equals_Param), t)),
18457   
18458    [ not(equals(Equals_Param, shelf)),
18459      not(equals(Equals_Param, table)),
18460      not(equals(Equals_Param, floor))
18461    ]).
18462
18463 /*  equals(Equals_Param4, cat) :-
18464       ( (   not(equals(Equals_Param4, food1))
18465         ;   not(equals(Equals_Param5, table))
18466         ),
18467         (   not(equals(Equals_Param4, food2))
18468         ;   not(equals(Equals_Param5, shelf))
18469         )
18470       ),
18471       holds_at(on(Equals_Param4, Equals_Param5), 0).
18472 */
18473axiom(equals(Equals_Param4, cat),
18474   
18475    [ not(equals(Equals_Param4, food2)),
18476      not(equals(Equals_Param4, food1)),
18477      holds_at(on(Equals_Param4, Equals_Param5), t)
18478    ]).
18479axiom(equals(Equals_Param4, cat),
18480   
18481    [ not(equals(Equals_Param5, shelf)),
18482      not(equals(Equals_Param4, food1)),
18483      holds_at(on(Equals_Param4, Equals_Param5), t)
18484    ]).
18485axiom(equals(Equals_Param4, cat),
18486   
18487    [ not(equals(Equals_Param4, food2)),
18488      not(equals(Equals_Param5, table)),
18489      holds_at(on(Equals_Param4, Equals_Param5), t)
18490    ]).
18491axiom(equals(Equals_Param4, cat),
18492   
18493    [ not(equals(Equals_Param5, shelf)),
18494      not(equals(Equals_Param5, table)),
18495      holds_at(on(Equals_Param4, Equals_Param5), t)
18496    ]).
18497
18498 /*  equals(Equals_Param6, floor) :-
18499       ( (   not(equals(Equals_Param7, food1))
18500         ;   not(equals(Equals_Param6, table))
18501         ),
18502         (   not(equals(Equals_Param7, food2))
18503         ;   not(equals(Equals_Param6, shelf))
18504         )
18505       ),
18506       holds_at(on(Equals_Param7, Equals_Param6), 0).
18507 */
18508axiom(equals(Equals_Param6, floor),
18509   
18510    [ not(equals(Equals_Param7, food2)),
18511      not(equals(Equals_Param7, food1)),
18512      holds_at(on(Equals_Param7, Equals_Param6), t)
18513    ]).
18514axiom(equals(Equals_Param6, floor),
18515   
18516    [ not(equals(Equals_Param6, shelf)),
18517      not(equals(Equals_Param7, food1)),
18518      holds_at(on(Equals_Param7, Equals_Param6), t)
18519    ]).
18520axiom(equals(Equals_Param6, floor),
18521   
18522    [ not(equals(Equals_Param7, food2)),
18523      not(equals(Equals_Param6, table)),
18524      holds_at(on(Equals_Param7, Equals_Param6), t)
18525    ]).
18526axiom(equals(Equals_Param6, floor),
18527   
18528    [ not(equals(Equals_Param6, shelf)),
18529      not(equals(Equals_Param6, table)),
18530      holds_at(on(Equals_Param7, Equals_Param6), t)
18531    ]).
18532
18533 /*  equals(Equals_Param8, food1) :-
18534       (   not(equals(Equals_Param8, food2))
18535       ;   not(equals(Equals_Param9, shelf))
18536       ),
18537       (   not(equals(Equals_Param8, cat))
18538       ;   not(equals(Equals_Param9, floor))
18539       ),
18540       holds_at(on(Equals_Param8, Equals_Param9), 0).
18541 */
18542axiom(equals(Equals_Param8, food1),
18543   
18544    [ not(equals(Equals_Param8, cat)),
18545      not(equals(Equals_Param8, food2)),
18546      holds_at(on(Equals_Param8, Equals_Param9), t)
18547    ]).
18548axiom(equals(Equals_Param8, food1),
18549   
18550    [ not(equals(Equals_Param9, floor)),
18551      not(equals(Equals_Param8, food2)),
18552      holds_at(on(Equals_Param8, Equals_Param9), t)
18553    ]).
18554axiom(equals(Equals_Param8, food1),
18555   
18556    [ not(equals(Equals_Param8, cat)),
18557      not(equals(Equals_Param9, shelf)),
18558      holds_at(on(Equals_Param8, Equals_Param9), t)
18559    ]).
18560axiom(equals(Equals_Param8, food1),
18561   
18562    [ not(equals(Equals_Param9, floor)),
18563      not(equals(Equals_Param9, shelf)),
18564      holds_at(on(Equals_Param8, Equals_Param9), t)
18565    ]).
18566
18567 /*  equals(Equals_Param10, table) :-
18568       (   not(equals(Equals_Param11, food2))
18569       ;   not(equals(Equals_Param10, shelf))
18570       ),
18571       (   not(equals(Equals_Param11, cat))
18572       ;   not(equals(Equals_Param10, floor))
18573       ),
18574       holds_at(on(Equals_Param11, Equals_Param10), 0).
18575 */
18576axiom(equals(Equals_Param10, table),
18577   
18578    [ not(equals(Equals_Param11, cat)),
18579      not(equals(Equals_Param11, food2)),
18580      holds_at(on(Equals_Param11, Equals_Param10), t)
18581    ]).
18582axiom(equals(Equals_Param10, table),
18583   
18584    [ not(equals(Equals_Param10, floor)),
18585      not(equals(Equals_Param11, food2)),
18586      holds_at(on(Equals_Param11, Equals_Param10), t)
18587    ]).
18588axiom(equals(Equals_Param10, table),
18589   
18590    [ not(equals(Equals_Param11, cat)),
18591      not(equals(Equals_Param10, shelf)),
18592      holds_at(on(Equals_Param11, Equals_Param10), t)
18593    ]).
18594axiom(equals(Equals_Param10, table),
18595   
18596    [ not(equals(Equals_Param10, floor)),
18597      not(equals(Equals_Param10, shelf)),
18598      holds_at(on(Equals_Param11, Equals_Param10), t)
18599    ]).
18600
18601 /*  equals(Equals_Param12, food2) :-
18602       (   not(equals(Equals_Param12, food1))
18603       ;   not(equals(Equals_Param13, table))
18604       ),
18605       (   not(equals(Equals_Param12, cat))
18606       ;   not(equals(Equals_Param13, floor))
18607       ),
18608       holds_at(on(Equals_Param12, Equals_Param13), 0).
18609 */
18610axiom(equals(Equals_Param12, food2),
18611   
18612    [ not(equals(Equals_Param12, cat)),
18613      not(equals(Equals_Param12, food1)),
18614      holds_at(on(Equals_Param12, Equals_Param13), t)
18615    ]).
18616axiom(equals(Equals_Param12, food2),
18617   
18618    [ not(equals(Equals_Param13, floor)),
18619      not(equals(Equals_Param12, food1)),
18620      holds_at(on(Equals_Param12, Equals_Param13), t)
18621    ]).
18622axiom(equals(Equals_Param12, food2),
18623   
18624    [ not(equals(Equals_Param12, cat)),
18625      not(equals(Equals_Param13, table)),
18626      holds_at(on(Equals_Param12, Equals_Param13), t)
18627    ]).
18628axiom(equals(Equals_Param12, food2),
18629   
18630    [ not(equals(Equals_Param13, floor)),
18631      not(equals(Equals_Param13, table)),
18632      holds_at(on(Equals_Param12, Equals_Param13), t)
18633    ]).
18634
18635 /*  equals(Equals_Param14, shelf) :-
18636       (   not(equals(Equals_Param15, food1))
18637       ;   not(equals(Equals_Param14, table))
18638       ),
18639       (   not(equals(Equals_Param15, cat))
18640       ;   not(equals(Equals_Param14, floor))
18641       ),
18642       holds_at(on(Equals_Param15, Equals_Param14), 0).
18643 */
18644axiom(equals(Equals_Param14, shelf),
18645   
18646    [ not(equals(Equals_Param15, cat)),
18647      not(equals(Equals_Param15, food1)),
18648      holds_at(on(Equals_Param15, Equals_Param14), t)
18649    ]).
18650axiom(equals(Equals_Param14, shelf),
18651   
18652    [ not(equals(Equals_Param14, floor)),
18653      not(equals(Equals_Param15, food1)),
18654      holds_at(on(Equals_Param15, Equals_Param14), t)
18655    ]).
18656axiom(equals(Equals_Param14, shelf),
18657   
18658    [ not(equals(Equals_Param15, cat)),
18659      not(equals(Equals_Param14, table)),
18660      holds_at(on(Equals_Param15, Equals_Param14), t)
18661    ]).
18662axiom(equals(Equals_Param14, shelf),
18663   
18664    [ not(equals(Equals_Param14, floor)),
18665      not(equals(Equals_Param14, table)),
18666      holds_at(on(Equals_Param15, Equals_Param14), t)
18667    ]).
18668
18669
18670% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6219
18671% [surface1,surface2]
18672 % HoldsAt(CanJump(surface1,surface2),0) <->
18673% (surface1=Floor & surface2=Chair) |
18674% (surface1=Chair & surface2=Table) |
18675% (surface1=Shelf & surface2=Table).
18676
18677 /*  holds_at(canJump(Surface1, Surface2), 0) <->
18678       (   Surface1=floor,
18679           Surface2=chair
18680       ;   Surface1=chair,
18681           Surface2=(table)
18682       ;   Surface1=shelf,
18683           Surface2=(table)
18684       ).
18685 */
18686% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6222
18687axiom(holds_at(canJump(Surface1, Surface2), t),
18688    [equals(Surface1, floor), equals(Surface2, chair)]).
18689axiom(holds_at(canJump(Surface1, Surface2), t),
18690    [equals(Surface1, chair), equals(Surface2, table)]).
18691axiom(holds_at(canJump(Surface1, Surface2), t),
18692    [equals(Surface1, shelf), equals(Surface2, table)]).
18693
18694 /*   if(holds_at(canJump(Surface1, Surface2), 0),
18695          (Surface1=floor, Surface2=chair;Surface1=chair, Surface2=(table);Surface1=shelf, Surface2=(table))).
18696 */
18697
18698 /*  not(holds_at(canJump(CanJump_Param, Equals_Param), 0)) :-
18699       (   not(equals(CanJump_Param, floor))
18700       ;   not(equals(Equals_Param, chair))
18701       ),
18702       (   not(equals(CanJump_Param, chair))
18703       ;   not(equals(Equals_Param, table))
18704       ),
18705       (   not(equals(CanJump_Param, shelf))
18706       ;   not(equals(Equals_Param, table))
18707       ).
18708 */
18709axiom(not(holds_at(canJump(CanJump_Param, Equals_Param), t)),
18710   
18711    [ not(equals(CanJump_Param, shelf)),
18712      not(equals(CanJump_Param, chair)),
18713      not(equals(CanJump_Param, floor))
18714    ]).
18715axiom(not(holds_at(canJump(CanJump_Param, Equals_Param), t)),
18716   
18717    [ not(equals(Equals_Param, table)),
18718      not(equals(CanJump_Param, chair)),
18719      not(equals(CanJump_Param, floor))
18720    ]).
18721axiom(not(holds_at(canJump(CanJump_Param, Equals_Param), t)),
18722   
18723    [ not(equals(CanJump_Param, shelf)),
18724      not(equals(Equals_Param, table)),
18725      not(equals(CanJump_Param, floor))
18726    ]).
18727axiom(not(holds_at(canJump(CanJump_Param, Equals_Param), t)),
18728   
18729    [ not(equals(Equals_Param, table)),
18730      not(equals(Equals_Param, table)),
18731      not(equals(CanJump_Param, floor))
18732    ]).
18733axiom(not(holds_at(canJump(CanJump_Param, Equals_Param), t)),
18734   
18735    [ not(equals(CanJump_Param, shelf)),
18736      not(equals(CanJump_Param, chair)),
18737      not(equals(Equals_Param, chair))
18738    ]).
18739axiom(not(holds_at(canJump(CanJump_Param, Equals_Param), t)),
18740   
18741    [ not(equals(Equals_Param, table)),
18742      not(equals(CanJump_Param, chair)),
18743      not(equals(Equals_Param, chair))
18744    ]).
18745axiom(not(holds_at(canJump(CanJump_Param, Equals_Param), t)),
18746   
18747    [ not(equals(CanJump_Param, shelf)),
18748      not(equals(Equals_Param, table)),
18749      not(equals(Equals_Param, chair))
18750    ]).
18751axiom(not(holds_at(canJump(CanJump_Param, Equals_Param), t)),
18752   
18753    [ not(equals(Equals_Param, table)),
18754      not(equals(Equals_Param, table)),
18755      not(equals(Equals_Param, chair))
18756    ]).
18757
18758 /*  equals(Equals_Param4, floor) :-
18759       ( (   not(equals(Equals_Param4, chair))
18760         ;   not(equals(Equals_Param5, table))
18761         ),
18762         (   not(equals(Equals_Param4, shelf))
18763         ;   not(equals(Equals_Param5, table))
18764         )
18765       ),
18766       holds_at(canJump(Equals_Param4, Equals_Param5), 0).
18767 */
18768axiom(equals(Equals_Param4, floor),
18769   
18770    [ not(equals(Equals_Param4, shelf)),
18771      not(equals(Equals_Param4, chair)),
18772      holds_at(canJump(Equals_Param4, Equals_Param5), t)
18773    ]).
18774axiom(equals(Equals_Param4, floor),
18775   
18776    [ not(equals(Equals_Param5, table)),
18777      not(equals(Equals_Param4, chair)),
18778      holds_at(canJump(Equals_Param4, Equals_Param5), t)
18779    ]).
18780axiom(equals(Equals_Param4, floor),
18781   
18782    [ not(equals(Equals_Param4, shelf)),
18783      not(equals(Equals_Param5, table)),
18784      holds_at(canJump(Equals_Param4, Equals_Param5), t)
18785    ]).
18786axiom(equals(Equals_Param4, floor),
18787   
18788    [ not(equals(Equals_Param5, table)),
18789      not(equals(Equals_Param5, table)),
18790      holds_at(canJump(Equals_Param4, Equals_Param5), t)
18791    ]).
18792
18793 /*  equals(Equals_Param6, chair) :-
18794       ( (   not(equals(Equals_Param7, chair))
18795         ;   not(equals(Equals_Param6, table))
18796         ),
18797         (   not(equals(Equals_Param7, shelf))
18798         ;   not(equals(Equals_Param6, table))
18799         )
18800       ),
18801       holds_at(canJump(Equals_Param7, Equals_Param6), 0).
18802 */
18803axiom(equals(Equals_Param6, chair),
18804   
18805    [ not(equals(Equals_Param7, shelf)),
18806      not(equals(Equals_Param7, chair)),
18807      holds_at(canJump(Equals_Param7, Equals_Param6), t)
18808    ]).
18809axiom(equals(Equals_Param6, chair),
18810   
18811    [ not(equals(Equals_Param6, table)),
18812      not(equals(Equals_Param7, chair)),
18813      holds_at(canJump(Equals_Param7, Equals_Param6), t)
18814    ]).
18815axiom(equals(Equals_Param6, chair),
18816   
18817    [ not(equals(Equals_Param7, shelf)),
18818      not(equals(Equals_Param6, table)),
18819      holds_at(canJump(Equals_Param7, Equals_Param6), t)
18820    ]).
18821axiom(equals(Equals_Param6, chair),
18822   
18823    [ not(equals(Equals_Param6, table)),
18824      not(equals(Equals_Param6, table)),
18825      holds_at(canJump(Equals_Param7, Equals_Param6), t)
18826    ]).
18827
18828 /*  equals(Equals_Param8, chair) :-
18829       (   not(equals(Equals_Param8, shelf))
18830       ;   not(equals(Equals_Param9, table))
18831       ),
18832       (   not(equals(Equals_Param8, floor))
18833       ;   not(equals(Equals_Param9, chair))
18834       ),
18835       holds_at(canJump(Equals_Param8, Equals_Param9), 0).
18836 */
18837axiom(equals(Equals_Param8, chair),
18838   
18839    [ not(equals(Equals_Param8, floor)),
18840      not(equals(Equals_Param8, shelf)),
18841      holds_at(canJump(Equals_Param8, Equals_Param9), t)
18842    ]).
18843axiom(equals(Equals_Param8, chair),
18844   
18845    [ not(equals(Equals_Param9, chair)),
18846      not(equals(Equals_Param8, shelf)),
18847      holds_at(canJump(Equals_Param8, Equals_Param9), t)
18848    ]).
18849axiom(equals(Equals_Param8, chair),
18850   
18851    [ not(equals(Equals_Param8, floor)),
18852      not(equals(Equals_Param9, table)),
18853      holds_at(canJump(Equals_Param8, Equals_Param9), t)
18854    ]).
18855axiom(equals(Equals_Param8, chair),
18856   
18857    [ not(equals(Equals_Param9, chair)),
18858      not(equals(Equals_Param9, table)),
18859      holds_at(canJump(Equals_Param8, Equals_Param9), t)
18860    ]).
18861
18862 /*  equals(Equals_Param10, table) :-
18863       (   not(equals(Equals_Param11, shelf))
18864       ;   not(equals(Equals_Param10, table))
18865       ),
18866       (   not(equals(Equals_Param11, floor))
18867       ;   not(equals(Equals_Param10, chair))
18868       ),
18869       holds_at(canJump(Equals_Param11, Equals_Param10), 0).
18870 */
18871axiom(equals(Equals_Param10, table),
18872   
18873    [ not(equals(Equals_Param11, floor)),
18874      not(equals(Equals_Param11, shelf)),
18875      holds_at(canJump(Equals_Param11, Equals_Param10), t)
18876    ]).
18877axiom(equals(Equals_Param10, table),
18878   
18879    [ not(equals(Equals_Param10, chair)),
18880      not(equals(Equals_Param11, shelf)),
18881      holds_at(canJump(Equals_Param11, Equals_Param10), t)
18882    ]).
18883axiom(equals(Equals_Param10, table),
18884   
18885    [ not(equals(Equals_Param11, floor)),
18886      not(equals(Equals_Param10, table)),
18887      holds_at(canJump(Equals_Param11, Equals_Param10), t)
18888    ]).
18889axiom(equals(Equals_Param10, table),
18890   
18891    [ not(equals(Equals_Param10, chair)),
18892      not(equals(Equals_Param10, table)),
18893      holds_at(canJump(Equals_Param11, Equals_Param10), t)
18894    ]).
18895
18896 /*  equals(Equals_Param12, shelf) :-
18897       (   not(equals(Equals_Param12, chair))
18898       ;   not(equals(Equals_Param13, table))
18899       ),
18900       (   not(equals(Equals_Param12, floor))
18901       ;   not(equals(Equals_Param13, chair))
18902       ),
18903       holds_at(canJump(Equals_Param12, Equals_Param13), 0).
18904 */
18905axiom(equals(Equals_Param12, shelf),
18906   
18907    [ not(equals(Equals_Param12, floor)),
18908      not(equals(Equals_Param12, chair)),
18909      holds_at(canJump(Equals_Param12, Equals_Param13), t)
18910    ]).
18911axiom(equals(Equals_Param12, shelf),
18912   
18913    [ not(equals(Equals_Param13, chair)),
18914      not(equals(Equals_Param12, chair)),
18915      holds_at(canJump(Equals_Param12, Equals_Param13), t)
18916    ]).
18917axiom(equals(Equals_Param12, shelf),
18918   
18919    [ not(equals(Equals_Param12, floor)),
18920      not(equals(Equals_Param13, table)),
18921      holds_at(canJump(Equals_Param12, Equals_Param13), t)
18922    ]).
18923axiom(equals(Equals_Param12, shelf),
18924   
18925    [ not(equals(Equals_Param13, chair)),
18926      not(equals(Equals_Param13, table)),
18927      holds_at(canJump(Equals_Param12, Equals_Param13), t)
18928    ]).
18929
18930 /*  equals(Equals_Param14, table) :-
18931       (   not(equals(Equals_Param15, chair))
18932       ;   not(equals(Equals_Param14, table))
18933       ),
18934       (   not(equals(Equals_Param15, floor))
18935       ;   not(equals(Equals_Param14, chair))
18936       ),
18937       holds_at(canJump(Equals_Param15, Equals_Param14), 0).
18938 */
18939axiom(equals(Equals_Param14, table),
18940   
18941    [ not(equals(Equals_Param15, floor)),
18942      not(equals(Equals_Param15, chair)),
18943      holds_at(canJump(Equals_Param15, Equals_Param14), t)
18944    ]).
18945axiom(equals(Equals_Param14, table),
18946   
18947    [ not(equals(Equals_Param14, chair)),
18948      not(equals(Equals_Param15, chair)),
18949      holds_at(canJump(Equals_Param15, Equals_Param14), t)
18950    ]).
18951axiom(equals(Equals_Param14, table),
18952   
18953    [ not(equals(Equals_Param15, floor)),
18954      not(equals(Equals_Param14, table)),
18955      holds_at(canJump(Equals_Param15, Equals_Param14), t)
18956    ]).
18957axiom(equals(Equals_Param14, table),
18958   
18959    [ not(equals(Equals_Param14, chair)),
18960      not(equals(Equals_Param14, table)),
18961      holds_at(canJump(Equals_Param15, Equals_Param14), t)
18962    ]).
18963
18964
18965% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6224
18966% [agent,object,surface]
18967% HoldsAt(Believe(agent,BOn(object,surface)),0) <->
18968% (agent=Cat & object=Cat & surface=Floor) |
18969% (agent=Cat & object=Food1 & surface=Table).
18970
18971 /*  holds_at(believe(Agent, bOn(Object, Surface)), 0) <->
18972       (   Agent=cat,
18973           Object=cat,
18974           Surface=floor
18975       ;   Agent=cat,
18976           Object=food1,
18977           Surface=(table)
18978       ).
18979 */
18980% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6227
18981axiom(holds_at(believe(Agent, bOn(Object, Surface)), t),
18982   
18983    [ equals(Agent, cat),
18984      equals(Object, cat),
18985      equals(Surface, floor)
18986    ]).
18987axiom(holds_at(believe(Agent, bOn(Object, Surface)), t),
18988   
18989    [ equals(Agent, cat),
18990      equals(Object, food1),
18991      equals(Surface, table)
18992    ]).
18993
18994 /*   if(holds_at(believe(Agent, bOn(Object, Surface)), 0),
18995          (Agent=cat, Object=cat, Surface=floor;Agent=cat, Object=food1, Surface=(table))).
18996 */
18997
18998 /*  not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), 0)) :-
18999       (   not(equals(Believe_Param, cat))
19000       ;   not(equals(BOn_Param, cat))
19001       ;   not(equals(Equals_Param, floor))
19002       ),
19003       (   not(equals(Believe_Param, cat))
19004       ;   not(equals(BOn_Param, food1))
19005       ;   not(equals(Equals_Param, table))
19006       ).
19007 */
19008axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19009   
19010    [ not(equals(Believe_Param, cat)),
19011      not(equals(Believe_Param, cat))
19012    ]).
19013axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19014    [not(equals(BOn_Param, food1)), not(equals(Believe_Param, cat))]).
19015axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19016   
19017    [ not(equals(Equals_Param, table)),
19018      not(equals(Believe_Param, cat))
19019    ]).
19020axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19021    [not(equals(Believe_Param, cat)), not(equals(BOn_Param, cat))]).
19022axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19023    [not(equals(BOn_Param, food1)), not(equals(BOn_Param, cat))]).
19024axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19025    [not(equals(Equals_Param, table)), not(equals(BOn_Param, cat))]).
19026axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19027   
19028    [ not(equals(Believe_Param, cat)),
19029      not(equals(Equals_Param, floor))
19030    ]).
19031axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19032    [not(equals(BOn_Param, food1)), not(equals(Equals_Param, floor))]).
19033axiom(not(holds_at(believe(Believe_Param, bOn(BOn_Param, Equals_Param)), t)),
19034   
19035    [ not(equals(Equals_Param, table)),
19036      not(equals(Equals_Param, floor))
19037    ]).
19038
19039 /*  equals(Equals_Param6, cat) :-
19040       (   not(equals(Equals_Param6, cat))
19041       ;   not(equals(Equals_Param7, food1))
19042       ;   not(equals(Equals_Param8, table))
19043       ),
19044       holds_at(believe(Equals_Param6,
19045                        bOn(Equals_Param7, Equals_Param8)),
19046                0).
19047 */
19048axiom(equals(Equals_Param6, cat),
19049   
19050    [ not(equals(Equals_Param6, cat)),
19051      holds_at(believe(Equals_Param6,
19052                       bOn(Equals_Param7, Equals_Param8)),
19053               t)
19054    ]).
19055axiom(equals(Equals_Param6, cat),
19056   
19057    [ not(equals(Equals_Param7, food1)),
19058      holds_at(believe(Equals_Param6,
19059                       bOn(Equals_Param7, Equals_Param8)),
19060               t)
19061    ]).
19062axiom(equals(Equals_Param6, cat),
19063   
19064    [ not(equals(Equals_Param8, table)),
19065      holds_at(believe(Equals_Param6,
19066                       bOn(Equals_Param7, Equals_Param8)),
19067               t)
19068    ]).
19069
19070 /*  equals(Equals_Param9, cat) :-
19071       (   not(equals(Equals_Param10, cat))
19072       ;   not(equals(Equals_Param9, food1))
19073       ;   not(equals(Equals_Param11, table))
19074       ),
19075       holds_at(believe(Equals_Param10,
19076                        bOn(Equals_Param9, Equals_Param11)),
19077                0).
19078 */
19079axiom(equals(Equals_Param9, cat),
19080   
19081    [ not(equals(Equals_Param10, cat)),
19082      holds_at(believe(Equals_Param10,
19083                       bOn(Equals_Param9, Equals_Param11)),
19084               t)
19085    ]).
19086axiom(equals(Equals_Param9, cat),
19087   
19088    [ not(equals(Equals_Param9, food1)),
19089      holds_at(believe(Equals_Param10,
19090                       bOn(Equals_Param9, Equals_Param11)),
19091               t)
19092    ]).
19093axiom(equals(Equals_Param9, cat),
19094   
19095    [ not(equals(Equals_Param11, table)),
19096      holds_at(believe(Equals_Param10,
19097                       bOn(Equals_Param9, Equals_Param11)),
19098               t)
19099    ]).
19100
19101 /*  equals(Equals_Param12, floor) :-
19102       (   not(equals(Equals_Param13, cat))
19103       ;   not(equals(Equals_Param14, food1))
19104       ;   not(equals(Equals_Param12, table))
19105       ),
19106       holds_at(believe(Equals_Param13,
19107                        bOn(Equals_Param14, Equals_Param12)),
19108                0).
19109 */
19110axiom(equals(Equals_Param12, floor),
19111   
19112    [ not(equals(Equals_Param13, cat)),
19113      holds_at(believe(Equals_Param13,
19114                       bOn(Equals_Param14, Equals_Param12)),
19115               t)
19116    ]).
19117axiom(equals(Equals_Param12, floor),
19118   
19119    [ not(equals(Equals_Param14, food1)),
19120      holds_at(believe(Equals_Param13,
19121                       bOn(Equals_Param14, Equals_Param12)),
19122               t)
19123    ]).
19124axiom(equals(Equals_Param12, floor),
19125   
19126    [ not(equals(Equals_Param12, table)),
19127      holds_at(believe(Equals_Param13,
19128                       bOn(Equals_Param14, Equals_Param12)),
19129               t)
19130    ]).
19131
19132 /*  equals(Equals_Param15, cat) :-
19133       (   not(equals(Equals_Param15, cat))
19134       ;   not(equals(Equals_Param16, cat))
19135       ;   not(equals(Equals_Param17, floor))
19136       ),
19137       holds_at(believe(Equals_Param15,
19138                        bOn(Equals_Param16, Equals_Param17)),
19139                0).
19140 */
19141axiom(equals(Equals_Param15, cat),
19142   
19143    [ not(equals(Equals_Param15, cat)),
19144      holds_at(believe(Equals_Param15,
19145                       bOn(Equals_Param16, Equals_Param17)),
19146               t)
19147    ]).
19148axiom(equals(Equals_Param15, cat),
19149   
19150    [ not(equals(Equals_Param16, cat)),
19151      holds_at(believe(Equals_Param15,
19152                       bOn(Equals_Param16, Equals_Param17)),
19153               t)
19154    ]).
19155axiom(equals(Equals_Param15, cat),
19156   
19157    [ not(equals(Equals_Param17, floor)),
19158      holds_at(believe(Equals_Param15,
19159                       bOn(Equals_Param16, Equals_Param17)),
19160               t)
19161    ]).
19162
19163 /*  equals(Equals_Param18, food1) :-
19164       (   not(equals(Equals_Param19, cat))
19165       ;   not(equals(Equals_Param18, cat))
19166       ;   not(equals(Equals_Param20, floor))
19167       ),
19168       holds_at(believe(Equals_Param19,
19169                        bOn(Equals_Param18, Equals_Param20)),
19170                0).
19171 */
19172axiom(equals(Equals_Param18, food1),
19173   
19174    [ not(equals(Equals_Param19, cat)),
19175      holds_at(believe(Equals_Param19,
19176                       bOn(Equals_Param18, Equals_Param20)),
19177               t)
19178    ]).
19179axiom(equals(Equals_Param18, food1),
19180   
19181    [ not(equals(Equals_Param18, cat)),
19182      holds_at(believe(Equals_Param19,
19183                       bOn(Equals_Param18, Equals_Param20)),
19184               t)
19185    ]).
19186axiom(equals(Equals_Param18, food1),
19187   
19188    [ not(equals(Equals_Param20, floor)),
19189      holds_at(believe(Equals_Param19,
19190                       bOn(Equals_Param18, Equals_Param20)),
19191               t)
19192    ]).
19193
19194 /*  equals(Equals_Param21, table) :-
19195       (   not(equals(Equals_Param22, cat))
19196       ;   not(equals(Equals_Param23, cat))
19197       ;   not(equals(Equals_Param21, floor))
19198       ),
19199       holds_at(believe(Equals_Param22,
19200                        bOn(Equals_Param23, Equals_Param21)),
19201                0).
19202 */
19203axiom(equals(Equals_Param21, table),
19204   
19205    [ not(equals(Equals_Param22, cat)),
19206      holds_at(believe(Equals_Param22,
19207                       bOn(Equals_Param23, Equals_Param21)),
19208               t)
19209    ]).
19210axiom(equals(Equals_Param21, table),
19211   
19212    [ not(equals(Equals_Param23, cat)),
19213      holds_at(believe(Equals_Param22,
19214                       bOn(Equals_Param23, Equals_Param21)),
19215               t)
19216    ]).
19217axiom(equals(Equals_Param21, table),
19218   
19219    [ not(equals(Equals_Param21, floor)),
19220      holds_at(believe(Equals_Param22,
19221                       bOn(Equals_Param23, Equals_Param21)),
19222               t)
19223    ]).
19224
19225
19226% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6229
19227% [agent,surface1,surface2]
19228% HoldsAt(Believe(agent,BCanJump(surface1,surface2)),0) <->
19229% (agent=Cat & surface1=Floor & surface2=Chair) |
19230% (agent=Cat & surface1=Chair & surface2=Table) |
19231% (agent=Cat & surface1=Shelf & surface2=Table).
19232
19233 /*  holds_at(believe(Agent, bCanJump(Surface1, Surface2)), 0) <->
19234       (   Agent=cat,
19235           Surface1=floor,
19236           Surface2=chair
19237       ;   Agent=cat,
19238           Surface1=chair,
19239           Surface2=(table)
19240       ;   Agent=cat,
19241           Surface1=shelf,
19242           Surface2=(table)
19243       ).
19244 */
19245% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6233
19246axiom(holds_at(believe(Agent, bCanJump(Surface1, Surface2)), t),
19247   
19248    [ equals(Agent, cat),
19249      equals(Surface1, floor),
19250      equals(Surface2, chair)
19251    ]).
19252axiom(holds_at(believe(Agent, bCanJump(Surface1, Surface2)), t),
19253   
19254    [ equals(Agent, cat),
19255      equals(Surface1, chair),
19256      equals(Surface2, table)
19257    ]).
19258axiom(holds_at(believe(Agent, bCanJump(Surface1, Surface2)), t),
19259   
19260    [ equals(Agent, cat),
19261      equals(Surface1, shelf),
19262      equals(Surface2, table)
19263    ]).
19264
19265 /*   if(holds_at(believe(Agent, bCanJump(Surface1, Surface2)), 0),
19266          (Agent=cat, Surface1=floor, Surface2=chair;Agent=cat, Surface1=chair, Surface2=(table);Agent=cat, Surface1=shelf, Surface2=(table))).
19267 */
19268
19269 /*  not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), 0)) :-
19270       (   not(equals(Believe_Param, cat))
19271       ;   not(equals(BCanJump_Param, floor))
19272       ;   not(equals(Equals_Param, chair))
19273       ),
19274       (   not(equals(Believe_Param, cat))
19275       ;   not(equals(BCanJump_Param, chair))
19276       ;   not(equals(Equals_Param, table))
19277       ),
19278       (   not(equals(Believe_Param, cat))
19279       ;   not(equals(BCanJump_Param, shelf))
19280       ;   not(equals(Equals_Param, table))
19281       ).
19282 */
19283axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19284   
19285    [ not(equals(Believe_Param, cat)),
19286      not(equals(Believe_Param, cat)),
19287      not(equals(Believe_Param, cat))
19288    ]).
19289axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19290   
19291    [ not(equals(BCanJump_Param, shelf)),
19292      not(equals(Believe_Param, cat)),
19293      not(equals(Believe_Param, cat))
19294    ]).
19295axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19296   
19297    [ not(equals(Equals_Param, table)),
19298      not(equals(Believe_Param, cat)),
19299      not(equals(Believe_Param, cat))
19300    ]).
19301axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19302   
19303    [ not(equals(Believe_Param, cat)),
19304      not(equals(BCanJump_Param, chair)),
19305      not(equals(Believe_Param, cat))
19306    ]).
19307axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19308   
19309    [ not(equals(BCanJump_Param, shelf)),
19310      not(equals(BCanJump_Param, chair)),
19311      not(equals(Believe_Param, cat))
19312    ]).
19313axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19314   
19315    [ not(equals(Equals_Param, table)),
19316      not(equals(BCanJump_Param, chair)),
19317      not(equals(Believe_Param, cat))
19318    ]).
19319axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19320   
19321    [ not(equals(Believe_Param, cat)),
19322      not(equals(Equals_Param, table)),
19323      not(equals(Believe_Param, cat))
19324    ]).
19325axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19326   
19327    [ not(equals(BCanJump_Param, shelf)),
19328      not(equals(Equals_Param, table)),
19329      not(equals(Believe_Param, cat))
19330    ]).
19331axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19332   
19333    [ not(equals(Equals_Param, table)),
19334      not(equals(Equals_Param, table)),
19335      not(equals(Believe_Param, cat))
19336    ]).
19337axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19338   
19339    [ not(equals(Believe_Param, cat)),
19340      not(equals(Believe_Param, cat)),
19341      not(equals(BCanJump_Param, floor))
19342    ]).
19343axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19344   
19345    [ not(equals(BCanJump_Param, shelf)),
19346      not(equals(Believe_Param, cat)),
19347      not(equals(BCanJump_Param, floor))
19348    ]).
19349axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19350   
19351    [ not(equals(Equals_Param, table)),
19352      not(equals(Believe_Param, cat)),
19353      not(equals(BCanJump_Param, floor))
19354    ]).
19355axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19356   
19357    [ not(equals(Believe_Param, cat)),
19358      not(equals(BCanJump_Param, chair)),
19359      not(equals(BCanJump_Param, floor))
19360    ]).
19361axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19362   
19363    [ not(equals(BCanJump_Param, shelf)),
19364      not(equals(BCanJump_Param, chair)),
19365      not(equals(BCanJump_Param, floor))
19366    ]).
19367axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19368   
19369    [ not(equals(Equals_Param, table)),
19370      not(equals(BCanJump_Param, chair)),
19371      not(equals(BCanJump_Param, floor))
19372    ]).
19373axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19374   
19375    [ not(equals(Believe_Param, cat)),
19376      not(equals(Equals_Param, table)),
19377      not(equals(BCanJump_Param, floor))
19378    ]).
19379axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19380   
19381    [ not(equals(BCanJump_Param, shelf)),
19382      not(equals(Equals_Param, table)),
19383      not(equals(BCanJump_Param, floor))
19384    ]).
19385axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19386   
19387    [ not(equals(Equals_Param, table)),
19388      not(equals(Equals_Param, table)),
19389      not(equals(BCanJump_Param, floor))
19390    ]).
19391axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19392   
19393    [ not(equals(Believe_Param, cat)),
19394      not(equals(Believe_Param, cat)),
19395      not(equals(Equals_Param, chair))
19396    ]).
19397axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19398   
19399    [ not(equals(BCanJump_Param, shelf)),
19400      not(equals(Believe_Param, cat)),
19401      not(equals(Equals_Param, chair))
19402    ]).
19403axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19404   
19405    [ not(equals(Equals_Param, table)),
19406      not(equals(Believe_Param, cat)),
19407      not(equals(Equals_Param, chair))
19408    ]).
19409axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19410   
19411    [ not(equals(Believe_Param, cat)),
19412      not(equals(BCanJump_Param, chair)),
19413      not(equals(Equals_Param, chair))
19414    ]).
19415axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19416   
19417    [ not(equals(BCanJump_Param, shelf)),
19418      not(equals(BCanJump_Param, chair)),
19419      not(equals(Equals_Param, chair))
19420    ]).
19421axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19422   
19423    [ not(equals(Equals_Param, table)),
19424      not(equals(BCanJump_Param, chair)),
19425      not(equals(Equals_Param, chair))
19426    ]).
19427axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19428   
19429    [ not(equals(Believe_Param, cat)),
19430      not(equals(Equals_Param, table)),
19431      not(equals(Equals_Param, chair))
19432    ]).
19433axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19434   
19435    [ not(equals(BCanJump_Param, shelf)),
19436      not(equals(Equals_Param, table)),
19437      not(equals(Equals_Param, chair))
19438    ]).
19439axiom(not(holds_at(believe(Believe_Param, bCanJump(BCanJump_Param, Equals_Param)), t)),
19440   
19441    [ not(equals(Equals_Param, table)),
19442      not(equals(Equals_Param, table)),
19443      not(equals(Equals_Param, chair))
19444    ]).
19445
19446 /*  equals(Equals_Param6, cat) :-
19447       ( (   not(equals(Equals_Param6, cat))
19448         ;   not(equals(Equals_Param7, chair))
19449         ;   not(equals(Equals_Param8, table))
19450         ),
19451         (   not(equals(Equals_Param6, cat))
19452         ;   not(equals(Equals_Param7, shelf))
19453         ;   not(equals(Equals_Param8, table))
19454         )
19455       ),
19456       holds_at(believe(Equals_Param6,
19457                        bCanJump(Equals_Param7, Equals_Param8)),
19458                0).
19459 */
19460axiom(equals(Equals_Param6, cat),
19461   
19462    [ not(equals(Equals_Param6, cat)),
19463      not(equals(Equals_Param6, cat)),
19464      holds_at(believe(Equals_Param6,
19465                       bCanJump(Equals_Param7, Equals_Param8)),
19466               t)
19467    ]).
19468axiom(equals(Equals_Param6, cat),
19469   
19470    [ not(equals(Equals_Param7, shelf)),
19471      not(equals(Equals_Param6, cat)),
19472      holds_at(believe(Equals_Param6,
19473                       bCanJump(Equals_Param7, Equals_Param8)),
19474               t)
19475    ]).
19476axiom(equals(Equals_Param6, cat),
19477   
19478    [ not(equals(Equals_Param8, table)),
19479      not(equals(Equals_Param6, cat)),
19480      holds_at(believe(Equals_Param6,
19481                       bCanJump(Equals_Param7, Equals_Param8)),
19482               t)
19483    ]).
19484axiom(equals(Equals_Param6, cat),
19485   
19486    [ not(equals(Equals_Param6, cat)),
19487      not(equals(Equals_Param7, chair)),
19488      holds_at(believe(Equals_Param6,
19489                       bCanJump(Equals_Param7, Equals_Param8)),
19490               t)
19491    ]).
19492axiom(equals(Equals_Param6, cat),
19493   
19494    [ not(equals(Equals_Param7, shelf)),
19495      not(equals(Equals_Param7, chair)),
19496      holds_at(believe(Equals_Param6,
19497                       bCanJump(Equals_Param7, Equals_Param8)),
19498               t)
19499    ]).
19500axiom(equals(Equals_Param6, cat),
19501   
19502    [ not(equals(Equals_Param8, table)),
19503      not(equals(Equals_Param7, chair)),
19504      holds_at(believe(Equals_Param6,
19505                       bCanJump(Equals_Param7, Equals_Param8)),
19506               t)
19507    ]).
19508axiom(equals(Equals_Param6, cat),
19509   
19510    [ not(equals(Equals_Param6, cat)),
19511      not(equals(Equals_Param8, table)),
19512      holds_at(believe(Equals_Param6,
19513                       bCanJump(Equals_Param7, Equals_Param8)),
19514               t)
19515    ]).
19516axiom(equals(Equals_Param6, cat),
19517   
19518    [ not(equals(Equals_Param7, shelf)),
19519      not(equals(Equals_Param8, table)),
19520      holds_at(believe(Equals_Param6,
19521                       bCanJump(Equals_Param7, Equals_Param8)),
19522               t)
19523    ]).
19524axiom(equals(Equals_Param6, cat),
19525   
19526    [ not(equals(Equals_Param8, table)),
19527      not(equals(Equals_Param8, table)),
19528      holds_at(believe(Equals_Param6,
19529                       bCanJump(Equals_Param7, Equals_Param8)),
19530               t)
19531    ]).
19532
19533 /*  equals(Equals_Param9, floor) :-
19534       ( (   not(equals(Equals_Param10, cat))
19535         ;   not(equals(Equals_Param9, chair))
19536         ;   not(equals(Equals_Param11, table))
19537         ),
19538         (   not(equals(Equals_Param10, cat))
19539         ;   not(equals(Equals_Param9, shelf))
19540         ;   not(equals(Equals_Param11, table))
19541         )
19542       ),
19543       holds_at(believe(Equals_Param10,
19544                        bCanJump(Equals_Param9, Equals_Param11)),
19545                0).
19546 */
19547axiom(equals(Equals_Param9, floor),
19548   
19549    [ not(equals(Equals_Param10, cat)),
19550      not(equals(Equals_Param10, cat)),
19551      holds_at(believe(Equals_Param10,
19552                       bCanJump(Equals_Param9, Equals_Param11)),
19553               t)
19554    ]).
19555axiom(equals(Equals_Param9, floor),
19556   
19557    [ not(equals(Equals_Param9, shelf)),
19558      not(equals(Equals_Param10, cat)),
19559      holds_at(believe(Equals_Param10,
19560                       bCanJump(Equals_Param9, Equals_Param11)),
19561               t)
19562    ]).
19563axiom(equals(Equals_Param9, floor),
19564   
19565    [ not(equals(Equals_Param11, table)),
19566      not(equals(Equals_Param10, cat)),
19567      holds_at(believe(Equals_Param10,
19568                       bCanJump(Equals_Param9, Equals_Param11)),
19569               t)
19570    ]).
19571axiom(equals(Equals_Param9, floor),
19572   
19573    [ not(equals(Equals_Param10, cat)),
19574      not(equals(Equals_Param9, chair)),
19575      holds_at(believe(Equals_Param10,
19576                       bCanJump(Equals_Param9, Equals_Param11)),
19577               t)
19578    ]).
19579axiom(equals(Equals_Param9, floor),
19580   
19581    [ not(equals(Equals_Param9, shelf)),
19582      not(equals(Equals_Param9, chair)),
19583      holds_at(believe(Equals_Param10,
19584                       bCanJump(Equals_Param9, Equals_Param11)),
19585               t)
19586    ]).
19587axiom(equals(Equals_Param9, floor),
19588   
19589    [ not(equals(Equals_Param11, table)),
19590      not(equals(Equals_Param9, chair)),
19591      holds_at(believe(Equals_Param10,
19592                       bCanJump(Equals_Param9, Equals_Param11)),
19593               t)
19594    ]).
19595axiom(equals(Equals_Param9, floor),
19596   
19597    [ not(equals(Equals_Param10, cat)),
19598      not(equals(Equals_Param11, table)),
19599      holds_at(believe(Equals_Param10,
19600                       bCanJump(Equals_Param9, Equals_Param11)),
19601               t)
19602    ]).
19603axiom(equals(Equals_Param9, floor),
19604   
19605    [ not(equals(Equals_Param9, shelf)),
19606      not(equals(Equals_Param11, table)),
19607      holds_at(believe(Equals_Param10,
19608                       bCanJump(Equals_Param9, Equals_Param11)),
19609               t)
19610    ]).
19611axiom(equals(Equals_Param9, floor),
19612   
19613    [ not(equals(Equals_Param11, table)),
19614      not(equals(Equals_Param11, table)),
19615      holds_at(believe(Equals_Param10,
19616                       bCanJump(Equals_Param9, Equals_Param11)),
19617               t)
19618    ]).
19619
19620 /*  equals(Equals_Param12, chair) :-
19621       ( (   not(equals(Equals_Param13, cat))
19622         ;   not(equals(Equals_Param14, chair))
19623         ;   not(equals(Equals_Param12, table))
19624         ),
19625         (   not(equals(Equals_Param13, cat))
19626         ;   not(equals(Equals_Param14, shelf))
19627         ;   not(equals(Equals_Param12, table))
19628         )
19629       ),
19630       holds_at(believe(Equals_Param13,
19631                        bCanJump(Equals_Param14, Equals_Param12)),
19632                0).
19633 */
19634axiom(equals(Equals_Param12, chair),
19635   
19636    [ not(equals(Equals_Param13, cat)),
19637      not(equals(Equals_Param13, cat)),
19638      holds_at(believe(Equals_Param13,
19639                       bCanJump(Equals_Param14, Equals_Param12)),
19640               t)
19641    ]).
19642axiom(equals(Equals_Param12, chair),
19643   
19644    [ not(equals(Equals_Param14, shelf)),
19645      not(equals(Equals_Param13, cat)),
19646      holds_at(believe(Equals_Param13,
19647                       bCanJump(Equals_Param14, Equals_Param12)),
19648               t)
19649    ]).
19650axiom(equals(Equals_Param12, chair),
19651   
19652    [ not(equals(Equals_Param12, table)),
19653      not(equals(Equals_Param13, cat)),
19654      holds_at(believe(Equals_Param13,
19655                       bCanJump(Equals_Param14, Equals_Param12)),
19656               t)
19657    ]).
19658axiom(equals(Equals_Param12, chair),
19659   
19660    [ not(equals(Equals_Param13, cat)),
19661      not(equals(Equals_Param14, chair)),
19662      holds_at(believe(Equals_Param13,
19663                       bCanJump(Equals_Param14, Equals_Param12)),
19664               t)
19665    ]).
19666axiom(equals(Equals_Param12, chair),
19667   
19668    [ not(equals(Equals_Param14, shelf)),
19669      not(equals(Equals_Param14, chair)),
19670      holds_at(believe(Equals_Param13,
19671                       bCanJump(Equals_Param14, Equals_Param12)),
19672               t)
19673    ]).
19674axiom(equals(Equals_Param12, chair),
19675   
19676    [ not(equals(Equals_Param12, table)),
19677      not(equals(Equals_Param14, chair)),
19678      holds_at(believe(Equals_Param13,
19679                       bCanJump(Equals_Param14, Equals_Param12)),
19680               t)
19681    ]).
19682axiom(equals(Equals_Param12, chair),
19683   
19684    [ not(equals(Equals_Param13, cat)),
19685      not(equals(Equals_Param12, table)),
19686      holds_at(believe(Equals_Param13,
19687                       bCanJump(Equals_Param14, Equals_Param12)),
19688               t)
19689    ]).
19690axiom(equals(Equals_Param12, chair),
19691   
19692    [ not(equals(Equals_Param14, shelf)),
19693      not(equals(Equals_Param12, table)),
19694      holds_at(believe(Equals_Param13,
19695                       bCanJump(Equals_Param14, Equals_Param12)),
19696               t)
19697    ]).
19698axiom(equals(Equals_Param12, chair),
19699   
19700    [ not(equals(Equals_Param12, table)),
19701      not(equals(Equals_Param12, table)),
19702      holds_at(believe(Equals_Param13,
19703                       bCanJump(Equals_Param14, Equals_Param12)),
19704               t)
19705    ]).
19706
19707 /*  equals(Equals_Param15, cat) :-
19708       (   not(equals(Equals_Param15, cat))
19709       ;   not(equals(Equals_Param16, shelf))
19710       ;   not(equals(Equals_Param17, table))
19711       ),
19712       (   not(equals(Equals_Param15, cat))
19713       ;   not(equals(Equals_Param16, floor))
19714       ;   not(equals(Equals_Param17, chair))
19715       ),
19716       holds_at(believe(Equals_Param15,
19717                        bCanJump(Equals_Param16, Equals_Param17)),
19718                0).
19719 */
19720axiom(equals(Equals_Param15, cat),
19721   
19722    [ not(equals(Equals_Param15, cat)),
19723      not(equals(Equals_Param15, cat)),
19724      holds_at(believe(Equals_Param15,
19725                       bCanJump(Equals_Param16, Equals_Param17)),
19726               t)
19727    ]).
19728axiom(equals(Equals_Param15, cat),
19729   
19730    [ not(equals(Equals_Param16, floor)),
19731      not(equals(Equals_Param15, cat)),
19732      holds_at(believe(Equals_Param15,
19733                       bCanJump(Equals_Param16, Equals_Param17)),
19734               t)
19735    ]).
19736axiom(equals(Equals_Param15, cat),
19737   
19738    [ not(equals(Equals_Param17, chair)),
19739      not(equals(Equals_Param15, cat)),
19740      holds_at(believe(Equals_Param15,
19741                       bCanJump(Equals_Param16, Equals_Param17)),
19742               t)
19743    ]).
19744axiom(equals(Equals_Param15, cat),
19745   
19746    [ not(equals(Equals_Param15, cat)),
19747      not(equals(Equals_Param16, shelf)),
19748      holds_at(believe(Equals_Param15,
19749                       bCanJump(Equals_Param16, Equals_Param17)),
19750               t)
19751    ]).
19752axiom(equals(Equals_Param15, cat),
19753   
19754    [ not(equals(Equals_Param16, floor)),
19755      not(equals(Equals_Param16, shelf)),
19756      holds_at(believe(Equals_Param15,
19757                       bCanJump(Equals_Param16, Equals_Param17)),
19758               t)
19759    ]).
19760axiom(equals(Equals_Param15, cat),
19761   
19762    [ not(equals(Equals_Param17, chair)),
19763      not(equals(Equals_Param16, shelf)),
19764      holds_at(believe(Equals_Param15,
19765                       bCanJump(Equals_Param16, Equals_Param17)),
19766               t)
19767    ]).
19768axiom(equals(Equals_Param15, cat),
19769   
19770    [ not(equals(Equals_Param15, cat)),
19771      not(equals(Equals_Param17, table)),
19772      holds_at(believe(Equals_Param15,
19773                       bCanJump(Equals_Param16, Equals_Param17)),
19774               t)
19775    ]).
19776axiom(equals(Equals_Param15, cat),
19777   
19778    [ not(equals(Equals_Param16, floor)),
19779      not(equals(Equals_Param17, table)),
19780      holds_at(believe(Equals_Param15,
19781                       bCanJump(Equals_Param16, Equals_Param17)),
19782               t)
19783    ]).
19784axiom(equals(Equals_Param15, cat),
19785   
19786    [ not(equals(Equals_Param17, chair)),
19787      not(equals(Equals_Param17, table)),
19788      holds_at(believe(Equals_Param15,
19789                       bCanJump(Equals_Param16, Equals_Param17)),
19790               t)
19791    ]).
19792
19793 /*  equals(Equals_Param18, chair) :-
19794       (   not(equals(Equals_Param19, cat))
19795       ;   not(equals(Equals_Param18, shelf))
19796       ;   not(equals(Equals_Param20, table))
19797       ),
19798       (   not(equals(Equals_Param19, cat))
19799       ;   not(equals(Equals_Param18, floor))
19800       ;   not(equals(Equals_Param20, chair))
19801       ),
19802       holds_at(believe(Equals_Param19,
19803                        bCanJump(Equals_Param18, Equals_Param20)),
19804                0).
19805 */
19806axiom(equals(Equals_Param18, chair),
19807   
19808    [ not(equals(Equals_Param19, cat)),
19809      not(equals(Equals_Param19, cat)),
19810      holds_at(believe(Equals_Param19,
19811                       bCanJump(Equals_Param18, Equals_Param20)),
19812               t)
19813    ]).
19814axiom(equals(Equals_Param18, chair),
19815   
19816    [ not(equals(Equals_Param18, floor)),
19817      not(equals(Equals_Param19, cat)),
19818      holds_at(believe(Equals_Param19,
19819                       bCanJump(Equals_Param18, Equals_Param20)),
19820               t)
19821    ]).
19822axiom(equals(Equals_Param18, chair),
19823   
19824    [ not(equals(Equals_Param20, chair)),
19825      not(equals(Equals_Param19, cat)),
19826      holds_at(believe(Equals_Param19,
19827                       bCanJump(Equals_Param18, Equals_Param20)),
19828               t)
19829    ]).
19830axiom(equals(Equals_Param18, chair),
19831   
19832    [ not(equals(Equals_Param19, cat)),
19833      not(equals(Equals_Param18, shelf)),
19834      holds_at(believe(Equals_Param19,
19835                       bCanJump(Equals_Param18, Equals_Param20)),
19836               t)
19837    ]).
19838axiom(equals(Equals_Param18, chair),
19839   
19840    [ not(equals(Equals_Param18, floor)),
19841      not(equals(Equals_Param18, shelf)),
19842      holds_at(believe(Equals_Param19,
19843                       bCanJump(Equals_Param18, Equals_Param20)),
19844               t)
19845    ]).
19846axiom(equals(Equals_Param18, chair),
19847   
19848    [ not(equals(Equals_Param20, chair)),
19849      not(equals(Equals_Param18, shelf)),
19850      holds_at(believe(Equals_Param19,
19851                       bCanJump(Equals_Param18, Equals_Param20)),
19852               t)
19853    ]).
19854axiom(equals(Equals_Param18, chair),
19855   
19856    [ not(equals(Equals_Param19, cat)),
19857      not(equals(Equals_Param20, table)),
19858      holds_at(believe(Equals_Param19,
19859                       bCanJump(Equals_Param18, Equals_Param20)),
19860               t)
19861    ]).
19862axiom(equals(Equals_Param18, chair),
19863   
19864    [ not(equals(Equals_Param18, floor)),
19865      not(equals(Equals_Param20, table)),
19866      holds_at(believe(Equals_Param19,
19867                       bCanJump(Equals_Param18, Equals_Param20)),
19868               t)
19869    ]).
19870axiom(equals(Equals_Param18, chair),
19871   
19872    [ not(equals(Equals_Param20, chair)),
19873      not(equals(Equals_Param20, table)),
19874      holds_at(believe(Equals_Param19,
19875                       bCanJump(Equals_Param18, Equals_Param20)),
19876               t)
19877    ]).
19878
19879 /*  equals(Equals_Param21, table) :-
19880       (   not(equals(Equals_Param22, cat))
19881       ;   not(equals(Equals_Param23, shelf))
19882       ;   not(equals(Equals_Param21, table))
19883       ),
19884       (   not(equals(Equals_Param22, cat))
19885       ;   not(equals(Equals_Param23, floor))
19886       ;   not(equals(Equals_Param21, chair))
19887       ),
19888       holds_at(believe(Equals_Param22,
19889                        bCanJump(Equals_Param23, Equals_Param21)),
19890                0).
19891 */
19892axiom(equals(Equals_Param21, table),
19893   
19894    [ not(equals(Equals_Param22, cat)),
19895      not(equals(Equals_Param22, cat)),
19896      holds_at(believe(Equals_Param22,
19897                       bCanJump(Equals_Param23, Equals_Param21)),
19898               t)
19899    ]).
19900axiom(equals(Equals_Param21, table),
19901   
19902    [ not(equals(Equals_Param23, floor)),
19903      not(equals(Equals_Param22, cat)),
19904      holds_at(believe(Equals_Param22,
19905                       bCanJump(Equals_Param23, Equals_Param21)),
19906               t)
19907    ]).
19908axiom(equals(Equals_Param21, table),
19909   
19910    [ not(equals(Equals_Param21, chair)),
19911      not(equals(Equals_Param22, cat)),
19912      holds_at(believe(Equals_Param22,
19913                       bCanJump(Equals_Param23, Equals_Param21)),
19914               t)
19915    ]).
19916axiom(equals(Equals_Param21, table),
19917   
19918    [ not(equals(Equals_Param22, cat)),
19919      not(equals(Equals_Param23, shelf)),
19920      holds_at(believe(Equals_Param22,
19921                       bCanJump(Equals_Param23, Equals_Param21)),
19922               t)
19923    ]).
19924axiom(equals(Equals_Param21, table),
19925   
19926    [ not(equals(Equals_Param23, floor)),
19927      not(equals(Equals_Param23, shelf)),
19928      holds_at(believe(Equals_Param22,
19929                       bCanJump(Equals_Param23, Equals_Param21)),
19930               t)
19931    ]).
19932axiom(equals(Equals_Param21, table),
19933   
19934    [ not(equals(Equals_Param21, chair)),
19935      not(equals(Equals_Param23, shelf)),
19936      holds_at(believe(Equals_Param22,
19937                       bCanJump(Equals_Param23, Equals_Param21)),
19938               t)
19939    ]).
19940axiom(equals(Equals_Param21, table),
19941   
19942    [ not(equals(Equals_Param22, cat)),
19943      not(equals(Equals_Param21, table)),
19944      holds_at(believe(Equals_Param22,
19945                       bCanJump(Equals_Param23, Equals_Param21)),
19946               t)
19947    ]).
19948axiom(equals(Equals_Param21, table),
19949   
19950    [ not(equals(Equals_Param23, floor)),
19951      not(equals(Equals_Param21, table)),
19952      holds_at(believe(Equals_Param22,
19953                       bCanJump(Equals_Param23, Equals_Param21)),
19954               t)
19955    ]).
19956axiom(equals(Equals_Param21, table),
19957   
19958    [ not(equals(Equals_Param21, chair)),
19959      not(equals(Equals_Param21, table)),
19960      holds_at(believe(Equals_Param22,
19961                       bCanJump(Equals_Param23, Equals_Param21)),
19962               t)
19963    ]).
19964
19965 /*  equals(Equals_Param24, cat) :-
19966       (   not(equals(Equals_Param24, cat))
19967       ;   not(equals(Equals_Param25, chair))
19968       ;   not(equals(Equals_Param26, table))
19969       ),
19970       (   not(equals(Equals_Param24, cat))
19971       ;   not(equals(Equals_Param25, floor))
19972       ;   not(equals(Equals_Param26, chair))
19973       ),
19974       holds_at(believe(Equals_Param24,
19975                        bCanJump(Equals_Param25, Equals_Param26)),
19976                0).
19977 */
19978axiom(equals(Equals_Param24, cat),
19979   
19980    [ not(equals(Equals_Param24, cat)),
19981      not(equals(Equals_Param24, cat)),
19982      holds_at(believe(Equals_Param24,
19983                       bCanJump(Equals_Param25, Equals_Param26)),
19984               t)
19985    ]).
19986axiom(equals(Equals_Param24, cat),
19987   
19988    [ not(equals(Equals_Param25, floor)),
19989      not(equals(Equals_Param24, cat)),
19990      holds_at(believe(Equals_Param24,
19991                       bCanJump(Equals_Param25, Equals_Param26)),
19992               t)
19993    ]).
19994axiom(equals(Equals_Param24, cat),
19995   
19996    [ not(equals(Equals_Param26, chair)),
19997      not(equals(Equals_Param24, cat)),
19998      holds_at(believe(Equals_Param24,
19999                       bCanJump(Equals_Param25, Equals_Param26)),
20000               t)
20001    ]).
20002axiom(equals(Equals_Param24, cat),
20003   
20004    [ not(equals(Equals_Param24, cat)),
20005      not(equals(Equals_Param25, chair)),
20006      holds_at(believe(Equals_Param24,
20007                       bCanJump(Equals_Param25, Equals_Param26)),
20008               t)
20009    ]).
20010axiom(equals(Equals_Param24, cat),
20011   
20012    [ not(equals(Equals_Param25, floor)),
20013      not(equals(Equals_Param25, chair)),
20014      holds_at(believe(Equals_Param24,
20015                       bCanJump(Equals_Param25, Equals_Param26)),
20016               t)
20017    ]).
20018axiom(equals(Equals_Param24, cat),
20019   
20020    [ not(equals(Equals_Param26, chair)),
20021      not(equals(Equals_Param25, chair)),
20022      holds_at(believe(Equals_Param24,
20023                       bCanJump(Equals_Param25, Equals_Param26)),
20024               t)
20025    ]).
20026axiom(equals(Equals_Param24, cat),
20027   
20028    [ not(equals(Equals_Param24, cat)),
20029      not(equals(Equals_Param26, table)),
20030      holds_at(believe(Equals_Param24,
20031                       bCanJump(Equals_Param25, Equals_Param26)),
20032               t)
20033    ]).
20034axiom(equals(Equals_Param24, cat),
20035   
20036    [ not(equals(Equals_Param25, floor)),
20037      not(equals(Equals_Param26, table)),
20038      holds_at(believe(Equals_Param24,
20039                       bCanJump(Equals_Param25, Equals_Param26)),
20040               t)
20041    ]).
20042axiom(equals(Equals_Param24, cat),
20043   
20044    [ not(equals(Equals_Param26, chair)),
20045      not(equals(Equals_Param26, table)),
20046      holds_at(believe(Equals_Param24,
20047                       bCanJump(Equals_Param25, Equals_Param26)),
20048               t)
20049    ]).
20050
20051 /*  equals(Equals_Param27, shelf) :-
20052       (   not(equals(Equals_Param28, cat))
20053       ;   not(equals(Equals_Param27, chair))
20054       ;   not(equals(Equals_Param29, table))
20055       ),
20056       (   not(equals(Equals_Param28, cat))
20057       ;   not(equals(Equals_Param27, floor))
20058       ;   not(equals(Equals_Param29, chair))
20059       ),
20060       holds_at(believe(Equals_Param28,
20061                        bCanJump(Equals_Param27, Equals_Param29)),
20062                0).
20063 */
20064axiom(equals(Equals_Param27, shelf),
20065   
20066    [ not(equals(Equals_Param28, cat)),
20067      not(equals(Equals_Param28, cat)),
20068      holds_at(believe(Equals_Param28,
20069                       bCanJump(Equals_Param27, Equals_Param29)),
20070               t)
20071    ]).
20072axiom(equals(Equals_Param27, shelf),
20073   
20074    [ not(equals(Equals_Param27, floor)),
20075      not(equals(Equals_Param28, cat)),
20076      holds_at(believe(Equals_Param28,
20077                       bCanJump(Equals_Param27, Equals_Param29)),
20078               t)
20079    ]).
20080axiom(equals(Equals_Param27, shelf),
20081   
20082    [ not(equals(Equals_Param29, chair)),
20083      not(equals(Equals_Param28, cat)),
20084      holds_at(believe(Equals_Param28,
20085                       bCanJump(Equals_Param27, Equals_Param29)),
20086               t)
20087    ]).
20088axiom(equals(Equals_Param27, shelf),
20089   
20090    [ not(equals(Equals_Param28, cat)),
20091      not(equals(Equals_Param27, chair)),
20092      holds_at(believe(Equals_Param28,
20093                       bCanJump(Equals_Param27, Equals_Param29)),
20094               t)
20095    ]).
20096axiom(equals(Equals_Param27, shelf),
20097   
20098    [ not(equals(Equals_Param27, floor)),
20099      not(equals(Equals_Param27, chair)),
20100      holds_at(believe(Equals_Param28,
20101                       bCanJump(Equals_Param27, Equals_Param29)),
20102               t)
20103    ]).
20104axiom(equals(Equals_Param27, shelf),
20105   
20106    [ not(equals(Equals_Param29, chair)),
20107      not(equals(Equals_Param27, chair)),
20108      holds_at(believe(Equals_Param28,
20109                       bCanJump(Equals_Param27, Equals_Param29)),
20110               t)
20111    ]).
20112axiom(equals(Equals_Param27, shelf),
20113   
20114    [ not(equals(Equals_Param28, cat)),
20115      not(equals(Equals_Param29, table)),
20116      holds_at(believe(Equals_Param28,
20117                       bCanJump(Equals_Param27, Equals_Param29)),
20118               t)
20119    ]).
20120axiom(equals(Equals_Param27, shelf),
20121   
20122    [ not(equals(Equals_Param27, floor)),
20123      not(equals(Equals_Param29, table)),
20124      holds_at(believe(Equals_Param28,
20125                       bCanJump(Equals_Param27, Equals_Param29)),
20126               t)
20127    ]).
20128axiom(equals(Equals_Param27, shelf),
20129   
20130    [ not(equals(Equals_Param29, chair)),
20131      not(equals(Equals_Param29, table)),
20132      holds_at(believe(Equals_Param28,
20133                       bCanJump(Equals_Param27, Equals_Param29)),
20134               t)
20135    ]).
20136
20137 /*  equals(Equals_Param30, table) :-
20138       (   not(equals(Equals_Param31, cat))
20139       ;   not(equals(Equals_Param32, chair))
20140       ;   not(equals(Equals_Param30, table))
20141       ),
20142       (   not(equals(Equals_Param31, cat))
20143       ;   not(equals(Equals_Param32, floor))
20144       ;   not(equals(Equals_Param30, chair))
20145       ),
20146       holds_at(believe(Equals_Param31,
20147                        bCanJump(Equals_Param32, Equals_Param30)),
20148                0).
20149 */
20150axiom(equals(Equals_Param30, table),
20151   
20152    [ not(equals(Equals_Param31, cat)),
20153      not(equals(Equals_Param31, cat)),
20154      holds_at(believe(Equals_Param31,
20155                       bCanJump(Equals_Param32, Equals_Param30)),
20156               t)
20157    ]).
20158axiom(equals(Equals_Param30, table),
20159   
20160    [ not(equals(Equals_Param32, floor)),
20161      not(equals(Equals_Param31, cat)),
20162      holds_at(believe(Equals_Param31,
20163                       bCanJump(Equals_Param32, Equals_Param30)),
20164               t)
20165    ]).
20166axiom(equals(Equals_Param30, table),
20167   
20168    [ not(equals(Equals_Param30, chair)),
20169      not(equals(Equals_Param31, cat)),
20170      holds_at(believe(Equals_Param31,
20171                       bCanJump(Equals_Param32, Equals_Param30)),
20172               t)
20173    ]).
20174axiom(equals(Equals_Param30, table),
20175   
20176    [ not(equals(Equals_Param31, cat)),
20177      not(equals(Equals_Param32, chair)),
20178      holds_at(believe(Equals_Param31,
20179                       bCanJump(Equals_Param32, Equals_Param30)),
20180               t)
20181    ]).
20182axiom(equals(Equals_Param30, table),
20183   
20184    [ not(equals(Equals_Param32, floor)),
20185      not(equals(Equals_Param32, chair)),
20186      holds_at(believe(Equals_Param31,
20187                       bCanJump(Equals_Param32, Equals_Param30)),
20188               t)
20189    ]).
20190axiom(equals(Equals_Param30, table),
20191   
20192    [ not(equals(Equals_Param30, chair)),
20193      not(equals(Equals_Param32, chair)),
20194      holds_at(believe(Equals_Param31,
20195                       bCanJump(Equals_Param32, Equals_Param30)),
20196               t)
20197    ]).
20198axiom(equals(Equals_Param30, table),
20199   
20200    [ not(equals(Equals_Param31, cat)),
20201      not(equals(Equals_Param30, table)),
20202      holds_at(believe(Equals_Param31,
20203                       bCanJump(Equals_Param32, Equals_Param30)),
20204               t)
20205    ]).
20206axiom(equals(Equals_Param30, table),
20207   
20208    [ not(equals(Equals_Param32, floor)),
20209      not(equals(Equals_Param30, table)),
20210      holds_at(believe(Equals_Param31,
20211                       bCanJump(Equals_Param32, Equals_Param30)),
20212               t)
20213    ]).
20214axiom(equals(Equals_Param30, table),
20215   
20216    [ not(equals(Equals_Param30, chair)),
20217      not(equals(Equals_Param30, table)),
20218      holds_at(believe(Equals_Param31,
20219                       bCanJump(Equals_Param32, Equals_Param30)),
20220               t)
20221    ]).
20222
20223
20224% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6235
20225% !HoldsAt(Believe(Cat,BSatiated(Cat)),0).
20226 %  not(initially(believe(cat,bSatiated(cat)))).
20227axiom(not(initially(believe(cat, bSatiated(cat)))),
20228    []).
20229
20230
20231% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6237
20232%; ADDED:
20233
20234
20235% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6238
20236% !HoldsAt(Satiated(Cat),0).
20237 %  not(initially(satiated(cat))).
20238axiom(not(initially(satiated(cat))),
20239    []).
20240
20241% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6240
20242% completion Happens
20243% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6241
20244==> completion(happens).
20245
20246% range time 0 7
20247% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6243
20248==> range(time,0,7).
20249
20250% range offset 1 1
20251% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6244
20252==> range(offset,1,1).
20253%; End of file.
20254%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20255%; FILE: examples/Mueller2006/Chapter11/Lottery.e
20256%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20257%;
20258%; Copyright (c) 2005 IBM Corporation and others.
20259%; All rights reserved. This program and the accompanying materials
20260%; are made available under the terms of the Common Public License v1.0
20261%; which accompanies this distribution, and is available at
20262%; http://www.eclipse.org/legal/cpl-v10.html
20263%;
20264%; Contributors:
20265%; IBM - Initial implementation
20266%;
20267%; @book{OrtonyCloreCollins:1988,
20268%;   author = "Andrew Ortony and Gerald L. Clore and Allan M. Collins",
20269%;   year = "1988",
20270%;   title = "The Cognitive Structure of Emotions",
20271%;   address = "Cambridge",
20272%;   publisher = "Cambridge University Press",
20273%; }
20274%;
20275%; @book{Mueller:2006,
20276%;   author = "Erik T. Mueller",
20277%;   year = "2006",
20278%;   title = "Commonsense Reasoning",
20279%;   address = "San Francisco",
20280%;   publisher = "Morgan Kaufmann/Elsevier",
20281%; }
20282%;
20283
20284% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6279
20285% option modeldiff on
20286% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6280
20287:- set_ec_option(modeldiff, on).20288
20289% load foundations/Root.e
20290
20291% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6282
20292% load foundations/EC.e
20293
20294% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6284
20295% sort agent
20296% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6285
20297==> sort(agent).
20298
20299% sort aboutevent
20300% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6286
20301==> sort(aboutevent).
20302
20303% sort desirability: integer
20304% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6287
20305==> subsort(desirability,integer).
20306
20307% agent Kate, Lisa
20308% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6289
20309==> t(agent,kate).
20310==> t(agent,lisa).
20311
20312% aboutevent WinLotteryKate, WinLotteryLisa
20313% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6290
20314==> t(aboutevent,winLotteryKate).
20315==> t(aboutevent,winLotteryLisa).
20316
20317% fluent Joy(agent,aboutevent)
20318 %  fluent(joy(agent,aboutevent)).
20319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6292
20320==> mpred_prop(joy(agent,aboutevent),fluent).
20321==> meta_argtypes(joy(agent,aboutevent)).
20322
20323% fluent Desirability(agent,agent,aboutevent,desirability)
20324 %  fluent(desirability(agent,agent,aboutevent,desirability)).
20325% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6293
20326==> mpred_prop(desirability(agent,agent,aboutevent,desirability),
20327	       fluent).
20328==> meta_argtypes(desirability(agent,agent,aboutevent,desirability)).
20329
20330% fluent Believe(agent,aboutevent)
20331 %  fluent(believe(agent,aboutevent)).
20332% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6294
20333==> mpred_prop(believe(agent,aboutevent),fluent).
20334==> meta_argtypes(believe(agent,aboutevent)).
20335
20336% fluent Like(agent,agent)
20337 %  fluent(like(agent,agent)).
20338% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6295
20339==> mpred_prop(like(agent,agent),fluent).
20340==> meta_argtypes(like(agent,agent)).
20341
20342% fluent HappyFor(agent,agent,aboutevent)
20343 %  fluent(happyFor(agent,agent,aboutevent)).
20344% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6296
20345==> mpred_prop(happyFor(agent,agent,aboutevent),fluent).
20346==> meta_argtypes(happyFor(agent,agent,aboutevent)).
20347
20348% event WinLottery(agent)
20349 %  event(winLottery(agent)).
20350% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6298
20351==> mpred_prop(winLottery(agent),event).
20352==> meta_argtypes(winLottery(agent)).
20353
20354% event AddJoy(agent,aboutevent)
20355 %  event(addJoy(agent,aboutevent)).
20356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6299
20357==> mpred_prop(addJoy(agent,aboutevent),event).
20358==> meta_argtypes(addJoy(agent,aboutevent)).
20359
20360% event AddHappyFor(agent,agent,aboutevent)
20361 %  event(addHappyFor(agent,agent,aboutevent)).
20362% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6300
20363==> mpred_prop(addHappyFor(agent,agent,aboutevent),event).
20364==> meta_argtypes(addHappyFor(agent,agent,aboutevent)).
20365
20366
20367% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6301
20368%; Sigma
20369% [agent,aboutevent,time]
20370% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6304
20371% Initiates(AddJoy(agent,aboutevent),Joy(agent,aboutevent),time).
20372axiom(initiates(addJoy(Agent, Aboutevent), joy(Agent, Aboutevent), Time),
20373    []).
20374
20375
20376% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6306
20377% [agent1,agent2,aboutevent,time]
20378% Initiates(AddHappyFor(agent1,agent2,aboutevent),
20379%           HappyFor(agent1,agent2,aboutevent),
20380%           time).
20381% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6309
20382axiom(initiates(addHappyFor(Agent1, Agent2, Aboutevent), happyFor(Agent1, Agent2, Aboutevent), Time),
20383    []).
20384
20385
20386% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6311
20387% [agent1,agent2,aboutevent,time]
20388% (agent1=Kate & aboutevent=WinLotteryKate) |
20389% (agent1=Lisa & aboutevent=WinLotteryLisa) ->
20390% Initiates(WinLottery(agent1),Believe(agent2,aboutevent),time).
20391% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6314
20392axiom(initiates(winLottery(Agent1), believe(Agent2, Aboutevent), Time),
20393    [equals(Agent1, kate), equals(Aboutevent, winLotteryKate)]).
20394axiom(initiates(winLottery(Agent1), believe(Agent2, Aboutevent), Time),
20395    [equals(Agent1, lisa), equals(Aboutevent, winLotteryLisa)]).
20396
20397
20398% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6316
20399%; Delta
20400% [agent,aboutevent,desirability,time]
20401% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6319
20402% !HoldsAt(Joy(agent,aboutevent),time) &
20403% HoldsAt(Desirability(agent,agent,aboutevent,desirability),time) &
20404% desirability=1 &
20405% HoldsAt(Believe(agent,aboutevent),time) ->
20406% Happens(AddJoy(agent,aboutevent),time).
20407% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6323
20408axiom(happens(addJoy(Agent, Aboutevent), Time),
20409   
20410    [ not(holds_at(joy(Agent, Aboutevent), Time)),
20411      holds_at(desirability(Agent,
20412                            Agent,
20413                            Aboutevent,
20414                            Desirability),
20415               Time),
20416      equals(Desirability, 1),
20417      holds_at(believe(Agent, Aboutevent), Time)
20418    ]).
20419
20420
20421% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6325
20422% [agent1,agent2,aboutevent,desirability1,desirability2,time]
20423% !HoldsAt(HappyFor(agent1,agent2,aboutevent),time) &
20424% HoldsAt(Desirability(agent1,agent2,aboutevent,desirability1),time) &
20425% desirability1=1 &
20426% HoldsAt(Desirability(agent1,agent1,aboutevent,desirability2),time) &
20427% desirability2=1 &
20428% HoldsAt(Like(agent1,agent2),time) &
20429% HoldsAt(Believe(agent1,aboutevent),time) &
20430% agent1 != agent2 ->
20431% Happens(AddHappyFor(agent1,agent2,aboutevent),time).
20432% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6334
20433axiom(happens(addHappyFor(Agent1, Agent2, Aboutevent), Time),
20434   
20435    [ not(holds_at(happyFor(Agent1, Agent2, Aboutevent),
20436                   Time)),
20437      holds_at(desirability(Agent1,
20438                            Agent2,
20439                            Aboutevent,
20440                            Desirability1),
20441               Time),
20442      equals(Desirability1, 1),
20443      holds_at(desirability(Agent1,
20444                            Agent1,
20445                            Aboutevent,
20446                            Desirability2),
20447               Time),
20448      equals(Desirability2, 1),
20449      holds_at(like(Agent1, Agent2), Time),
20450      holds_at(believe(Agent1, Aboutevent), Time),
20451      dif(Agent1, Agent2)
20452    ]).
20453
20454
20455% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6336
20456% Happens(WinLottery(Kate),0).
20457axiom(happens(winLottery(kate), t),
20458    [is_time(0)]).
20459
20460
20461% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6338
20462%; Psi
20463% [agent1,agent2,aboutevent,desirability1,desirability2,time]
20464% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6341
20465% HoldsAt(Desirability(agent1,agent2,aboutevent,desirability1),time) &
20466% HoldsAt(Desirability(agent1,agent2,aboutevent,desirability2),time) ->
20467% desirability1 = desirability2.
20468% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6343
20469axiom(Desirability1=Desirability2,
20470   
20471    [ holds_at(desirability(Agent1,
20472                            Agent2,
20473                            Aboutevent,
20474                            Desirability1),
20475               Time),
20476      holds_at(desirability(Agent1,
20477                            Agent2,
20478                            Aboutevent,
20479                            Desirability2),
20480               Time)
20481    ]).
20482
20483
20484% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6345
20485%; Gamma
20486% [agent,aboutevent]
20487 % !HoldsAt(Joy(agent,aboutevent),0).
20488 %  not(initially(joy(Agent,Aboutevent))).
20489% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6347
20490axiom(not(initially(joy(Joy_Param, Joy_Ret))),
20491    []).
20492
20493
20494% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6348
20495% [agent1,agent2,aboutevent]
20496 % !HoldsAt(HappyFor(agent1,agent2,aboutevent),0).
20497 %  not(initially(happyFor(Agent1,Agent2,Aboutevent))).
20498axiom(not(initially(happyFor(HappyFor_Param, _, HappyFor_Ret))),
20499    []).
20500
20501
20502% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6349
20503% [aboutevent]
20504 % !HoldsAt(Believe(Kate,aboutevent),0).
20505 %  not(initially(believe(kate,Aboutevent))).
20506axiom(not(initially(believe(kate, Believe_Ret))),
20507    []).
20508
20509
20510% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6350
20511% [aboutevent]
20512 % !HoldsAt(Believe(Lisa,aboutevent),0).
20513 %  not(initially(believe(lisa,Aboutevent))).
20514axiom(not(initially(believe(lisa, Believe_Ret))),
20515    []).
20516
20517
20518% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6351
20519% [agent1,agent2,time]
20520 % HoldsAt(Like(agent1,agent2),time).
20521holds_at(like(Agent1,Agent2),Time).
20522
20523
20524% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6353
20525% [time]
20526 % HoldsAt(Desirability(Lisa,Kate,WinLotteryKate,1),time).
20527holds_at(desirability(lisa,kate,winLotteryKate,1),Time).
20528
20529
20530% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6354
20531% [time]
20532 % HoldsAt(Desirability(Kate,Kate,WinLotteryKate,1),time).
20533holds_at(desirability(kate,kate,winLotteryKate,1),Time).
20534
20535
20536% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6355
20537% [time]
20538 % HoldsAt(Desirability(Lisa,Lisa,WinLotteryKate,1),time).
20539holds_at(desirability(lisa,lisa,winLotteryKate,1),Time).
20540
20541
20542% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6356
20543% [time]
20544 % HoldsAt(Desirability(Kate,Kate,WinLotteryLisa,0),time).
20545holds_at(desirability(kate,kate,winLotteryLisa,0),Time).
20546
20547
20548% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6357
20549% [time]
20550 % HoldsAt(Desirability(Kate,Lisa,WinLotteryLisa,0),time).
20551holds_at(desirability(kate,lisa,winLotteryLisa,0),Time).
20552
20553
20554% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6358
20555% [time]
20556 % HoldsAt(Desirability(Kate,Kate,WinLotteryLisa,0),time).
20557holds_at(desirability(kate,kate,winLotteryLisa,0),Time).
20558
20559
20560% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6359
20561% [time]
20562 % HoldsAt(Desirability(Kate,Lisa,WinLotteryKate,0),time).
20563holds_at(desirability(kate,lisa,winLotteryKate,0),Time).
20564
20565
20566% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6360
20567% [time]
20568 % HoldsAt(Desirability(Lisa,Lisa,WinLotteryLisa,0),time).
20569holds_at(desirability(lisa,lisa,winLotteryLisa,0),Time).
20570
20571
20572% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6361
20573% [time]
20574 % HoldsAt(Desirability(Lisa,Kate,WinLotteryLisa,1),time).
20575holds_at(desirability(lisa,kate,winLotteryLisa,1),Time).
20576
20577% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6363
20578% completion Happens
20579% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6364
20580==> completion(happens).
20581
20582% range time 0 3
20583% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6366
20584==> range(time,0,3).
20585
20586% range desirability -1 1
20587% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6367
20588==> range(desirability,-1,1).
20589
20590% range offset 1 1
20591% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6368
20592==> range(offset,1,1).
20593%; End of file.
20594%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20595%; FILE: examples/Manual/Example1a.e
20596%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20597%;
20598%; Copyright (c) 2005 IBM Corporation and others.
20599%; All rights reserved. This program and the accompanying materials
20600%; are made available under the terms of the Common Public License v1.0
20601%; which accompanies this distribution, and is available at
20602%; http://www.eclipse.org/legal/cpl-v10.html
20603%;
20604%; Contributors:
20605%; IBM - Initial implementation
20606%;
20607%; deduction
20608
20609% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6388
20610% option timediff off
20611% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6389
20612:- set_ec_option(timediff, off).20613
20614% load foundations/Root.e
20615
20616% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6391
20617% load foundations/EC.e
20618
20619% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6393
20620% sort agent
20621% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6394
20622==> sort(agent).
20623
20624% fluent Awake(agent)
20625 %  fluent(awake(agent)).
20626% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6396
20627==> mpred_prop(awake(agent),fluent).
20628==> meta_argtypes(awake(agent)).
20629
20630% event WakeUp(agent)
20631 %  event(wakeUp(agent)).
20632% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6397
20633==> mpred_prop(wakeUp(agent),event).
20634==> meta_argtypes(wakeUp(agent)).
20635
20636
20637% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6398
20638% [agent,time]
20639 % Initiates(WakeUp(agent),Awake(agent),time).
20640axiom(initiates(wakeUp(Agent), awake(Agent), Time),
20641    []).
20642
20643% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6400
20644% agent James
20645% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6401
20646==> t(agent,james).
20647
20648
20649% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6401
20650% !HoldsAt(Awake(James),0).
20651 %  not(initially(awake(james))).
20652axiom(not(initially(awake(james))),
20653    []).
20654
20655% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6402
20656% Delta: 
20657next_axiom_uses(delta).
20658 
20659
20660
20661% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6402
20662% Happens(WakeUp(James),0).
20663axiom(happens(wakeUp(james), t),
20664    [is_time(0)]).
20665
20666% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6404
20667% completion Delta Happens
20668% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6405
20669==> completion(delta).
20670==> completion(happens).
20671
20672% range time 0 1
20673% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6407
20674==> range(time,0,1).
20675
20676% range offset 1 1
20677% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6408
20678==> range(offset,1,1).
20679%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20680%; FILE: examples/Manual/Example1.e
20681%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20682%;
20683%; Copyright (c) 2005 IBM Corporation and others.
20684%; All rights reserved. This program and the accompanying materials
20685%; are made available under the terms of the Common Public License v1.0
20686%; which accompanies this distribution, and is available at
20687%; http://www.eclipse.org/legal/cpl-v10.html
20688%;
20689%; Contributors:
20690%; IBM - Initial implementation
20691%;
20692%; deduction
20693
20694% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6426
20695% load foundations/Root.e
20696
20697% load foundations/EC.e
20698
20699% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6429
20700% sort agent
20701% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6430
20702==> sort(agent).
20703
20704% fluent Awake(agent)
20705 %  fluent(awake(agent)).
20706% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6432
20707==> mpred_prop(awake(agent),fluent).
20708==> meta_argtypes(awake(agent)).
20709
20710% event WakeUp(agent)
20711 %  event(wakeUp(agent)).
20712% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6433
20713==> mpred_prop(wakeUp(agent),event).
20714==> meta_argtypes(wakeUp(agent)).
20715
20716
20717% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6434
20718% [agent,time]
20719 % Initiates(WakeUp(agent),Awake(agent),time).
20720axiom(initiates(wakeUp(Agent), awake(Agent), Time),
20721    []).
20722
20723% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6436
20724% agent James
20725% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6437
20726==> t(agent,james).
20727
20728
20729% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6437
20730% !HoldsAt(Awake(James),0).
20731 %  not(initially(awake(james))).
20732axiom(not(initially(awake(james))),
20733    []).
20734
20735% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6438
20736% Delta: 
20737next_axiom_uses(delta).
20738 
20739
20740
20741% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6438
20742% Happens(WakeUp(James),0).
20743axiom(happens(wakeUp(james), t),
20744    [is_time(0)]).
20745
20746% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6440
20747% completion Delta Happens
20748% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6441
20749==> completion(delta).
20750==> completion(happens).
20751
20752% range time 0 1
20753% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6443
20754==> range(time,0,1).
20755
20756% range offset 1 1
20757% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6444
20758==> range(offset,1,1).
20759%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20760%; FILE: examples/Manual/Example4.e
20761%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20762%;
20763%; Copyright (c) 2005 IBM Corporation and others.
20764%; All rights reserved. This program and the accompanying materials
20765%; are made available under the terms of the Common Public License v1.0
20766%; which accompanies this distribution, and is available at
20767%; http://www.eclipse.org/legal/cpl-v10.html
20768%;
20769%; Contributors:
20770%; IBM - Initial implementation
20771%;
20772
20773% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6460
20774% load foundations/Root.e
20775
20776% load foundations/EC.e
20777
20778% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6463
20779% sort agent
20780% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6464
20781==> sort(agent).
20782
20783% fluent Awake(agent)
20784 %  fluent(awake(agent)).
20785% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6466
20786==> mpred_prop(awake(agent),fluent).
20787==> meta_argtypes(awake(agent)).
20788
20789% event WakeUp(agent)
20790 %  event(wakeUp(agent)).
20791% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6467
20792==> mpred_prop(wakeUp(agent),event).
20793==> meta_argtypes(wakeUp(agent)).
20794
20795
20796% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6468
20797% [agent,time]
20798 % Initiates(WakeUp(agent),Awake(agent),time).
20799axiom(initiates(wakeUp(Agent), awake(Agent), Time),
20800    []).
20801
20802
20803% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6469
20804% [agent,time]
20805 % Happens(WakeUp(agent),time) -> !HoldsAt(Awake(agent),time).
20806axiom(requires(wakeUp(Agent), Time),
20807    [not(holds_at(awake(Agent), Time))]).
20808
20809% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6471
20810% agent James, Jessie
20811% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6472
20812==> t(agent,james).
20813==> t(agent,jessie).
20814
20815
20816% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6472
20817% !HoldsAt(Awake(James),0).
20818 %  not(initially(awake(james))).
20819axiom(not(initially(awake(james))),
20820    []).
20821
20822
20823% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6473
20824% !HoldsAt(Awake(Jessie),0).
20825 %  not(initially(awake(jessie))).
20826axiom(not(initially(awake(jessie))),
20827    []).
20828
20829
20830% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6474
20831% HoldsAt(Awake(James),1).
20832holds_at(awake(james),1).
20833
20834% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6476
20835% range time 0 1
20836% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6477
20837==> range(time,0,1).
20838
20839% range offset 1 1
20840% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6478
20841==> range(offset,1,1).
20842%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20843%; FILE: examples/Manual/Example3.e
20844%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20845%;
20846%; Copyright (c) 2005 IBM Corporation and others.
20847%; All rights reserved. This program and the accompanying materials
20848%; are made available under the terms of the Common Public License v1.0
20849%; which accompanies this distribution, and is available at
20850%; http://www.eclipse.org/legal/cpl-v10.html
20851%;
20852%; Contributors:
20853%; IBM - Initial implementation
20854%;
20855
20856% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6494
20857% load foundations/Root.e
20858
20859% load foundations/EC.e
20860
20861% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6497
20862% sort agent
20863% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6498
20864==> sort(agent).
20865
20866% fluent Awake(agent)
20867 %  fluent(awake(agent)).
20868% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6500
20869==> mpred_prop(awake(agent),fluent).
20870==> meta_argtypes(awake(agent)).
20871
20872% event WakeUp(agent)
20873 %  event(wakeUp(agent)).
20874% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6501
20875==> mpred_prop(wakeUp(agent),event).
20876==> meta_argtypes(wakeUp(agent)).
20877
20878
20879% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6502
20880% [agent,time]
20881 % Initiates(WakeUp(agent),Awake(agent),time).
20882axiom(initiates(wakeUp(Agent), awake(Agent), Time),
20883    []).
20884
20885% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6504
20886% agent James, Jessie
20887% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6505
20888==> t(agent,james).
20889==> t(agent,jessie).
20890
20891
20892% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6505
20893% !HoldsAt(Awake(James),0).
20894 %  not(initially(awake(james))).
20895axiom(not(initially(awake(james))),
20896    []).
20897
20898
20899% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6506
20900% HoldsAt(Awake(James),1).
20901holds_at(awake(james),1).
20902
20903% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6508
20904% range time 0 1
20905% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6509
20906==> range(time,0,1).
20907
20908% range offset 1 1
20909% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6510
20910==> range(offset,1,1).
20911%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20912%; FILE: examples/Manual/Example2.e
20913%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20914%;
20915%; Copyright (c) 2005 IBM Corporation and others.
20916%; All rights reserved. This program and the accompanying materials
20917%; are made available under the terms of the Common Public License v1.0
20918%; which accompanies this distribution, and is available at
20919%; http://www.eclipse.org/legal/cpl-v10.html
20920%;
20921%; Contributors:
20922%; IBM - Initial implementation
20923%;
20924
20925% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6526
20926% load foundations/Root.e
20927
20928% load foundations/EC.e
20929
20930% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6529
20931% sort agent
20932% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6530
20933==> sort(agent).
20934
20935% fluent Awake(agent)
20936 %  fluent(awake(agent)).
20937% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6532
20938==> mpred_prop(awake(agent),fluent).
20939==> meta_argtypes(awake(agent)).
20940
20941% event WakeUp(agent)
20942 %  event(wakeUp(agent)).
20943% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6533
20944==> mpred_prop(wakeUp(agent),event).
20945==> meta_argtypes(wakeUp(agent)).
20946
20947
20948% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6534
20949% [agent,time]
20950 % Initiates(WakeUp(agent),Awake(agent),time).
20951axiom(initiates(wakeUp(Agent), awake(Agent), Time),
20952    []).
20953
20954% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6536
20955% agent James
20956% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6537
20957==> t(agent,james).
20958
20959
20960% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6537
20961% !HoldsAt(Awake(James),0).
20962 %  not(initially(awake(james))).
20963axiom(not(initially(awake(james))),
20964    []).
20965
20966
20967% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6538
20968% HoldsAt(Awake(James),1).
20969holds_at(awake(james),1).
20970
20971% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6540
20972% range time 0 1
20973% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6541
20974==> range(time,0,1).
20975
20976% range offset 1 1
20977% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6542
20978==> range(offset,1,1).
20979%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20980%; FILE: examples/Mueller2004b/RunningAndDriving2.e
20981%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
20982%;
20983%; Copyright (c) 2005 IBM Corporation and others.
20984%; All rights reserved. This program and the accompanying materials
20985%; are made available under the terms of the Common Public License v1.0
20986%; which accompanies this distribution, and is available at
20987%; http://www.eclipse.org/legal/cpl-v10.html
20988%;
20989%; Contributors:
20990%; IBM - Initial implementation
20991%;
20992%; @inproceedings{Mueller:2004b,
20993%;   author = "Erik T. Mueller",
20994%;   year = "2004",
20995%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
20996%;   editor = "Valerie Barr and Zdravko Markov",
20997%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
20998%;   pages = "147--152",
20999%;   address = "Menlo Park, CA",
21000%;   publisher = "AAAI Press",
21001%; }
21002%;
21003
21004% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6570
21005% load foundations/Root.e
21006
21007% load foundations/EC.e
21008
21009% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6573
21010% sort agent
21011% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6574
21012==> sort(agent).
21013
21014% fluent Tired(agent)
21015 %  fluent(tired(agent)).
21016% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6576
21017==> mpred_prop(tired(agent),fluent).
21018==> meta_argtypes(tired(agent)).
21019
21020% event Move(agent)
21021 %  event(move(agent)).
21022% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6578
21023==> mpred_prop(move(agent),event).
21024==> meta_argtypes(move(agent)).
21025
21026% event Run(agent)
21027 %  event(run(agent)).
21028% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6579
21029==> mpred_prop(run(agent),event).
21030==> meta_argtypes(run(agent)).
21031
21032% event Drive(agent)
21033 %  event(drive(agent)).
21034% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6580
21035==> mpred_prop(drive(agent),event).
21036==> meta_argtypes(drive(agent)).
21037
21038
21039% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6581
21040% [agent,time]
21041% Happens(Move(agent),time) ->
21042% Happens(Run(agent),time) | Happens(Drive(agent),time).
21043
21044 /*   if(happens(move(Agent), Time),
21045          (happens(run(Agent), Time);happens(drive(Agent), Time))).
21046 */
21047
21048 /*  happens(run(Run_Ret), Maptime) :-
21049       not(happens(drive(Run_Ret), Maptime)),
21050       happens(move(Run_Ret), Maptime).
21051 */
21052% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6583
21053axiom(happens(run(Run_Ret), Maptime),
21054   
21055    [ not(happens(drive(Run_Ret), Maptime)),
21056      happens(move(Run_Ret), Maptime)
21057    ]).
21058
21059 /*  happens(drive(Drive_Ret), Maptime4) :-
21060       not(happens(run(Drive_Ret), Maptime4)),
21061       happens(move(Drive_Ret), Maptime4).
21062 */
21063axiom(happens(drive(Drive_Ret), Maptime4),
21064   
21065    [ not(happens(run(Drive_Ret), Maptime4)),
21066      happens(move(Drive_Ret), Maptime4)
21067    ]).
21068
21069 /*  not(happens(move(Move_Ret), Maptime6)) :-
21070       not(happens(run(Move_Ret), Maptime6)),
21071       not(happens(drive(Move_Ret), Maptime6)).
21072 */
21073axiom(not(happens(move(Move_Ret), Maptime6)),
21074   
21075    [ not(happens(run(Move_Ret), Maptime6)),
21076      not(happens(drive(Move_Ret), Maptime6))
21077    ]).
21078
21079% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6585
21080% xor Run, Drive
21081% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6586
21082xor([run,drive]).
21083
21084
21085% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6587
21086% [agent,time]
21087 % Initiates(Run(agent),Tired(agent),time).
21088axiom(initiates(run(Agent), tired(Agent), Time),
21089    []).
21090
21091% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6589
21092% agent James
21093% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6590
21094==> t(agent,james).
21095
21096
21097% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6591
21098% !HoldsAt(Tired(James),0).
21099 %  not(initially(tired(james))).
21100axiom(not(initially(tired(james))),
21101    []).
21102
21103
21104% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6592
21105% Happens(Move(James),0).
21106axiom(happens(move(james), t),
21107    [is_time(0)]).
21108
21109% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6594
21110% range time 0 1
21111% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6595
21112==> range(time,0,1).
21113
21114% range offset 1 1
21115% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6596
21116==> range(offset,1,1).
21117%; End of file.
21118%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21119%; FILE: examples/Mueller2004b/OffOn.e
21120%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21121%;
21122%; Copyright (c) 2005 IBM Corporation and others.
21123%; All rights reserved. This program and the accompanying materials
21124%; are made available under the terms of the Common Public License v1.0
21125%; which accompanies this distribution, and is available at
21126%; http://www.eclipse.org/legal/cpl-v10.html
21127%;
21128%; Contributors:
21129%; IBM - Initial implementation
21130%;
21131%; @inproceedings{Mueller:2004b,
21132%;   author = "Erik T. Mueller",
21133%;   year = "2004",
21134%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
21135%;   editor = "Valerie Barr and Zdravko Markov",
21136%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
21137%;   pages = "147--152",
21138%;   address = "Menlo Park, CA",
21139%;   publisher = "AAAI Press",
21140%; }
21141%;
21142
21143% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6626
21144% load foundations/Root.e
21145
21146% load foundations/EC.e
21147
21148% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6629
21149% sort agent
21150% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6630
21151==> sort(agent).
21152
21153% sort switch
21154% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6631
21155==> sort(switch).
21156
21157% fluent On(switch)
21158 %  fluent(on(switch)).
21159% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6633
21160==> mpred_prop(on(switch),fluent).
21161==> meta_argtypes(on(switch)).
21162
21163% fluent Off(switch)
21164 %  fluent(off(switch)).
21165% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6634
21166==> mpred_prop(off(switch),fluent).
21167==> meta_argtypes(off(switch)).
21168
21169% event TurnOn(agent,switch)
21170 %  event(turnOn(agent,switch)).
21171% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6635
21172==> mpred_prop(turnOn(agent,switch),event).
21173==> meta_argtypes(turnOn(agent,switch)).
21174
21175% event TurnOff(agent,switch)
21176 %  event(turnOff(agent,switch)).
21177% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6636
21178==> mpred_prop(turnOff(agent,switch),event).
21179==> meta_argtypes(turnOff(agent,switch)).
21180
21181% noninertial Off
21182% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6638
21183==> noninertial(off).
21184
21185
21186% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6639
21187% [switch,time]
21188 % HoldsAt(Off(switch),time) <-> !HoldsAt(On(switch),time).
21189
21190 /*  holds_at(off(Switch), Time) <->
21191       not(holds_at(on(Switch), Time)).
21192 */
21193axiom(holds_at(off(Switch), Time),
21194    [not(holds_at(on(Switch), Time))]).
21195axiom(not(holds_at(on(Switch), Time)),
21196    [holds_at(off(Switch), Time)]).
21197
21198
21199% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6641
21200% [agent,switch,time]
21201 % Initiates(TurnOn(agent,switch),On(switch),time).
21202axiom(initiates(turnOn(Agent, Switch), on(Switch), Time),
21203    []).
21204
21205
21206% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6642
21207% [agent,switch,time]
21208 % Terminates(TurnOff(agent,switch),On(switch),time).
21209axiom(terminates(turnOff(Agent, Switch), on(Switch), Time),
21210    []).
21211
21212% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6644
21213% agent James
21214% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6645
21215==> t(agent,james).
21216
21217% switch Switch1
21218% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6646
21219==> t(switch,switch1).
21220
21221
21222% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6647
21223% !HoldsAt(On(Switch1),0).
21224 %  not(initially(on(switch1))).
21225axiom(not(initially(on(switch1))),
21226    []).
21227
21228
21229% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6648
21230% Happens(TurnOn(James,Switch1),0).
21231axiom(happens(turnOn(james, switch1), t),
21232    [is_time(0)]).
21233
21234% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6650
21235% range time 0 1
21236% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6651
21237==> range(time,0,1).
21238
21239% range offset 1 1
21240% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6652
21241==> range(offset,1,1).
21242%; End of file.
21243%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21244%; FILE: examples/Mueller2004b/TV2.e
21245%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21246%;
21247%; Copyright (c) 2005 IBM Corporation and others.
21248%; All rights reserved. This program and the accompanying materials
21249%; are made available under the terms of the Common Public License v1.0
21250%; which accompanies this distribution, and is available at
21251%; http://www.eclipse.org/legal/cpl-v10.html
21252%;
21253%; Contributors:
21254%; IBM - Initial implementation
21255%;
21256%; @inproceedings{Mueller:2004b,
21257%;   author = "Erik T. Mueller",
21258%;   year = "2004",
21259%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
21260%;   editor = "Valerie Barr and Zdravko Markov",
21261%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
21262%;   pages = "147--152",
21263%;   address = "Menlo Park, CA",
21264%;   publisher = "AAAI Press",
21265%; }
21266%;
21267
21268% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6682
21269% load foundations/Root.e
21270
21271% load foundations/EC.e
21272
21273% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6685
21274% sort agent
21275% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6686
21276==> sort(agent).
21277
21278% sort switch
21279% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6687
21280==> sort(switch).
21281
21282% sort tv
21283% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6688
21284==> sort(tv).
21285
21286% function TVOf(switch): tv
21287 %  functional_predicate(tVOf(switch,tv)).
21288% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6690
21289==> mpred_prop(tVOf(switch,tv),functional_predicate).
21290==> meta_argtypes(tVOf(switch,tv)).
21291resultIsa(tVOf,tv).
21292
21293% fluent SwitchOn(switch)
21294 %  fluent(switchOn(switch)).
21295% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6691
21296==> mpred_prop(switchOn(switch),fluent).
21297==> meta_argtypes(switchOn(switch)).
21298
21299% fluent TVOn(tv)
21300 %  fluent(tVOn(tv)).
21301% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6692
21302==> mpred_prop(tVOn(tv),fluent).
21303==> meta_argtypes(tVOn(tv)).
21304
21305% fluent PluggedIn(tv)
21306 %  fluent(pluggedIn(tv)).
21307% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6693
21308==> mpred_prop(pluggedIn(tv),fluent).
21309==> meta_argtypes(pluggedIn(tv)).
21310
21311% event TurnOn(agent,switch)
21312 %  event(turnOn(agent,switch)).
21313% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6694
21314==> mpred_prop(turnOn(agent,switch),event).
21315==> meta_argtypes(turnOn(agent,switch)).
21316
21317% event TurnOff(agent,switch)
21318 %  event(turnOff(agent,switch)).
21319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6695
21320==> mpred_prop(turnOff(agent,switch),event).
21321==> meta_argtypes(turnOff(agent,switch)).
21322
21323
21324% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6696
21325% [agent,switch,time]
21326 % Initiates(TurnOn(agent,switch),SwitchOn(switch),time).
21327axiom(initiates(turnOn(Agent, Switch), switchOn(Switch), Time),
21328    []).
21329
21330
21331% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6698
21332% [agent,switch,tv,time]
21333% TVOf(switch)=tv & HoldsAt(PluggedIn(tv),time) ->
21334% Initiates(TurnOn(agent,switch),TVOn(tv),time).
21335% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6700
21336axiom(initiates(turnOn(Agent, Switch), tVOn(Tv), Time),
21337   
21338    [ equals(tVOf(Switch), Tv),
21339      holds_at(pluggedIn(Tv), Time)
21340    ]).
21341
21342% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6702
21343% agent James
21344% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6703
21345==> t(agent,james).
21346
21347% switch Switch1
21348% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6704
21349==> t(switch,switch1).
21350
21351% tv TV1
21352% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6705
21353==> t(tv,tv1).
21354
21355
21356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6706
21357% TVOf(Switch1)=TV1.
21358tVOf(switch1,tv1).
21359
21360
21361% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6707
21362% !HoldsAt(PluggedIn(TV1),0).
21363 %  not(initially(pluggedIn(tv1))).
21364axiom(not(initially(pluggedIn(tv1))),
21365    []).
21366
21367
21368% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6708
21369% !HoldsAt(SwitchOn(Switch1),0).
21370 %  not(initially(switchOn(switch1))).
21371axiom(not(initially(switchOn(switch1))),
21372    []).
21373
21374
21375% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6709
21376% !HoldsAt(TVOn(TV1),0).
21377 %  not(initially(tVOn(tv1))).
21378axiom(not(initially(tVOn(tv1))),
21379    []).
21380
21381
21382% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6710
21383% Happens(TurnOn(James,Switch1),0).
21384axiom(happens(turnOn(james, switch1), t),
21385    [is_time(0)]).
21386
21387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6712
21388% range time 0 1
21389% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6713
21390==> range(time,0,1).
21391
21392% range offset 1 1
21393% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6714
21394==> range(offset,1,1).
21395%; End of file.
21396%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21397%; FILE: examples/Mueller2004b/Approve.e
21398%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21399%;
21400%; Copyright (c) 2005 IBM Corporation and others.
21401%; All rights reserved. This program and the accompanying materials
21402%; are made available under the terms of the Common Public License v1.0
21403%; which accompanies this distribution, and is available at
21404%; http://www.eclipse.org/legal/cpl-v10.html
21405%;
21406%; Contributors:
21407%; IBM - Initial implementation
21408%;
21409%; example of concurrent events with cumulative or canceling effects
21410%;
21411%; @inproceedings{Mueller:2004b,
21412%;   author = "Erik T. Mueller",
21413%;   year = "2004",
21414%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
21415%;   editor = "Valerie Barr and Zdravko Markov",
21416%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
21417%;   pages = "147--152",
21418%;   address = "Menlo Park, CA",
21419%;   publisher = "AAAI Press",
21420%; }
21421%;
21422
21423% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6746
21424% load foundations/Root.e
21425
21426% load foundations/EC.e
21427
21428% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6749
21429% sort agent
21430% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6750
21431==> sort(agent).
21432
21433% event ApproveOf(agent,agent)
21434 %  event(approveOf(agent,agent)).
21435% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6752
21436==> mpred_prop(approveOf(agent,agent),event).
21437==> meta_argtypes(approveOf(agent,agent)).
21438
21439% event DisapproveOf(agent,agent)
21440 %  event(disapproveOf(agent,agent)).
21441% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6753
21442==> mpred_prop(disapproveOf(agent,agent),event).
21443==> meta_argtypes(disapproveOf(agent,agent)).
21444
21445% fluent Happy(agent)
21446 %  fluent(happy(agent)).
21447% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6754
21448==> mpred_prop(happy(agent),fluent).
21449==> meta_argtypes(happy(agent)).
21450
21451% fluent Confused(agent)
21452 %  fluent(confused(agent)).
21453% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6755
21454==> mpred_prop(confused(agent),fluent).
21455==> meta_argtypes(confused(agent)).
21456
21457
21458% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6756
21459% [agent1,agent2,time]
21460% !Happens(DisapproveOf(agent1,agent2),time) ->
21461% Initiates(ApproveOf(agent1,agent2),Happy(agent2),time).
21462% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6758
21463axiom(initiates(approveOf(Agent1, Agent2), happy(Agent2), Time),
21464    [not(happens(disapproveOf(Agent1, Agent2), Time))]).
21465
21466
21467% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6760
21468% [agent1,agent2,time]
21469% !Happens(ApproveOf(agent1,agent2),time) ->
21470% Terminates(DisapproveOf(agent1,agent2),Happy(agent2),time).
21471% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6762
21472axiom(terminates(disapproveOf(Agent1, Agent2), happy(Agent2), Time),
21473    [not(happens(approveOf(Agent1, Agent2), Time))]).
21474
21475
21476% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6764
21477% [agent1,agent2,time]
21478% Happens(DisapproveOf(agent1,agent2),time) ->
21479% Initiates(ApproveOf(agent1,agent2),Confused(agent2),time).
21480% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6766
21481axiom(requires(disapproveOf(Agent1, Agent2), Time),
21482   
21483    [ initiates(approveOf(Agent1, Agent2),
21484                confused(Agent2),
21485                Time)
21486    ]).
21487
21488% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6768
21489% agent James, Peter
21490% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6769
21491==> t(agent,james).
21492==> t(agent,peter).
21493
21494
21495% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6770
21496% [agent]
21497 % !HoldsAt(Happy(agent),0) & !HoldsAt(Confused(agent),0).
21498
21499 /*   not(holds_at(happy(Agent), 0)),
21500      not(holds_at(confused(Agent), 0)).
21501 */
21502axiom(not(holds_at(happy(Happy_Ret), t)),
21503    []).
21504axiom(not(holds_at(confused(Confused_Ret), t)),
21505    []).
21506
21507
21508% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6772
21509% Happens(ApproveOf(Peter,James),0).
21510axiom(happens(approveOf(peter, james), t),
21511    [is_time(0)]).
21512
21513
21514% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6773
21515% Happens(DisapproveOf(Peter,James),0).
21516axiom(happens(disapproveOf(peter, james), t),
21517    [is_time(0)]).
21518
21519% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6775
21520% completion Happens
21521% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6776
21522==> completion(happens).
21523
21524% range time 0 1
21525% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6778
21526==> range(time,0,1).
21527
21528% range offset 1 1
21529% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6779
21530==> range(offset,1,1).
21531%; End of file.
21532%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21533%; FILE: examples/Mueller2004b/Leaf.e
21534%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21535%;
21536%; Copyright (c) 2005 IBM Corporation and others.
21537%; All rights reserved. This program and the accompanying materials
21538%; are made available under the terms of the Common Public License v1.0
21539%; which accompanies this distribution, and is available at
21540%; http://www.eclipse.org/legal/cpl-v10.html
21541%;
21542%; Contributors:
21543%; IBM - Initial implementation
21544%;
21545%; @inproceedings{Mueller:2004b,
21546%;   author = "Erik T. Mueller",
21547%;   year = "2004",
21548%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
21549%;   editor = "Valerie Barr and Zdravko Markov",
21550%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
21551%;   pages = "147--152",
21552%;   address = "Menlo Park, CA",
21553%;   publisher = "AAAI Press",
21554%; }
21555%;
21556
21557% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6809
21558% option trajectory on
21559% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6810
21560:- set_ec_option(trajectory, on).21561
21562% load foundations/Root.e
21563
21564% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6812
21565% load foundations/EC.e
21566
21567% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6814
21568% sort object
21569% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6815
21570==> sort(object).
21571
21572% sort height: integer
21573% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6816
21574==> subsort(height,integer).
21575
21576% fluent Height(object,height)
21577 %  fluent(height(object,height)).
21578% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6818
21579==> mpred_prop(height(object,height),fluent).
21580==> meta_argtypes(height(object,height)).
21581
21582% fluent Falling(object)
21583 %  fluent(falling(object)).
21584% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6819
21585==> mpred_prop(falling(object),fluent).
21586==> meta_argtypes(falling(object)).
21587
21588% event StartFalling(object)
21589 %  event(startFalling(object)).
21590% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6820
21591==> mpred_prop(startFalling(object),event).
21592==> meta_argtypes(startFalling(object)).
21593
21594% event HitsGround(object)
21595 %  event(hitsGround(object)).
21596% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6821
21597==> mpred_prop(hitsGround(object),event).
21598==> meta_argtypes(hitsGround(object)).
21599
21600
21601% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6822
21602% [object,height1,height2,time]
21603% HoldsAt(Height(object,height1),time) &
21604% HoldsAt(Height(object,height2),time) ->
21605% height1=height2.
21606% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6825
21607axiom(Height1=Height2,
21608   
21609    [ holds_at(height(Object, Height1), Time),
21610      holds_at(height(Object, Height2), Time)
21611    ]).
21612
21613
21614% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6827
21615% [object,time]
21616% Initiates(StartFalling(object),Falling(object),time).
21617% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6828
21618axiom(initiates(startFalling(Object), falling(Object), Time),
21619    []).
21620
21621
21622% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6830
21623% [object,height,time]
21624% Releases(StartFalling(object),Height(object,height),time).
21625% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6831
21626axiom(releases(startFalling(Object), height(Object, Height), Time),
21627    []).
21628
21629
21630% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6833
21631% [object,height1,height2,offset,time]
21632% HoldsAt(Height(object,height1),time) &
21633% height2=height1-offset ->
21634% Trajectory(Falling(object),time,Height(object,height2),offset).
21635% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6836
21636axiom(trajectory(falling(Object), Time, height(Object, Height2), Offset),
21637   
21638    [ holds_at(height(Object, Height1), Time),
21639      equals(Height2, Height1-Offset)
21640    ]).
21641
21642
21643% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6838
21644% [object,time]
21645% HoldsAt(Falling(object),time) &
21646% HoldsAt(Height(object,0),time) ->
21647% Happens(HitsGround(object),time).
21648% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6841
21649axiom(happens(hitsGround(Object), Time),
21650   
21651    [ holds_at(falling(Object), Time),
21652      holds_at(height(Object, 0), Time)
21653    ]).
21654
21655
21656% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6843
21657%;[object,height1,height2,time]
21658%;HoldsAt(Height(object,height1),time) &
21659%;height1 != height2 ->
21660%;Terminates(HitsGround(object),Height(object,height2),time).
21661% [object,height,time]
21662% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6849
21663% HoldsAt(Height(object,height),time) ->
21664% Initiates(HitsGround(object),Height(object,height),time).
21665% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6850
21666axiom(initiates(hitsGround(Object), height(Object, Height), Time),
21667    [holds_at(height(Object, Height), Time)]).
21668
21669
21670% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6852
21671% [object,time]
21672% Terminates(HitsGround(object),Falling(object),time).
21673% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6853
21674axiom(terminates(hitsGround(Object), falling(Object), Time),
21675    []).
21676
21677% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6855
21678% object Leaf
21679% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6856
21680==> t(object,leaf).
21681
21682
21683% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6857
21684% !HoldsAt(Falling(Leaf),0).
21685 %  not(initially(falling(leaf))).
21686axiom(not(initially(falling(leaf))),
21687    []).
21688
21689
21690% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6858
21691% HoldsAt(Height(Leaf,4),0).
21692axiom(initially(height(leaf, 4)),
21693    []).
21694
21695
21696% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6859
21697% Happens(StartFalling(Leaf),2).
21698axiom(happens(startFalling(leaf), t2),
21699    [is_time(2), b(t, t2), ignore(t+2=t2)]).
21700
21701% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6861
21702% completion Happens
21703% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6862
21704==> completion(happens).
21705
21706% range time 0 7
21707% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6864
21708==> range(time,0,7).
21709
21710% range offset 1 4
21711% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6865
21712==> range(offset,1,4).
21713
21714% range height 0 4
21715% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6866
21716==> range(height,0,4).
21717%; End of file.
21718%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21719%; FILE: examples/Mueller2004b/RunningAndDriving1.e
21720%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21721%;
21722%; Copyright (c) 2005 IBM Corporation and others.
21723%; All rights reserved. This program and the accompanying materials
21724%; are made available under the terms of the Common Public License v1.0
21725%; which accompanies this distribution, and is available at
21726%; http://www.eclipse.org/legal/cpl-v10.html
21727%;
21728%; Contributors:
21729%; IBM - Initial implementation
21730%;
21731%; @inproceedings{Mueller:2004b,
21732%;   author = "Erik T. Mueller",
21733%;   year = "2004",
21734%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
21735%;   editor = "Valerie Barr and Zdravko Markov",
21736%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
21737%;   pages = "147--152",
21738%;   address = "Menlo Park, CA",
21739%;   publisher = "AAAI Press",
21740%; }
21741%;
21742
21743% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6896
21744% load foundations/Root.e
21745
21746% load foundations/EC.e
21747
21748% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6899
21749% sort agent
21750% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6900
21751==> sort(agent).
21752
21753% fluent Tired(agent)
21754 %  fluent(tired(agent)).
21755% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6902
21756==> mpred_prop(tired(agent),fluent).
21757==> meta_argtypes(tired(agent)).
21758
21759% event Move(agent)
21760 %  event(move(agent)).
21761% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6904
21762==> mpred_prop(move(agent),event).
21763==> meta_argtypes(move(agent)).
21764
21765% event Run(agent)
21766 %  event(run(agent)).
21767% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6905
21768==> mpred_prop(run(agent),event).
21769==> meta_argtypes(run(agent)).
21770
21771% event Drive(agent)
21772 %  event(drive(agent)).
21773% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6906
21774==> mpred_prop(drive(agent),event).
21775==> meta_argtypes(drive(agent)).
21776
21777
21778% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6907
21779% [agent,time]
21780% Happens(Move(agent),time) ->
21781% Happens(Run(agent),time) | Happens(Drive(agent),time).
21782
21783 /*   if(happens(move(Agent), Time),
21784          (happens(run(Agent), Time);happens(drive(Agent), Time))).
21785 */
21786
21787 /*  happens(run(Run_Ret), Maptime) :-
21788       not(happens(drive(Run_Ret), Maptime)),
21789       happens(move(Run_Ret), Maptime).
21790 */
21791% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6909
21792axiom(happens(run(Run_Ret), Maptime),
21793   
21794    [ not(happens(drive(Run_Ret), Maptime)),
21795      happens(move(Run_Ret), Maptime)
21796    ]).
21797
21798 /*  happens(drive(Drive_Ret), Maptime4) :-
21799       not(happens(run(Drive_Ret), Maptime4)),
21800       happens(move(Drive_Ret), Maptime4).
21801 */
21802axiom(happens(drive(Drive_Ret), Maptime4),
21803   
21804    [ not(happens(run(Drive_Ret), Maptime4)),
21805      happens(move(Drive_Ret), Maptime4)
21806    ]).
21807
21808 /*  not(happens(move(Move_Ret), Maptime6)) :-
21809       not(happens(run(Move_Ret), Maptime6)),
21810       not(happens(drive(Move_Ret), Maptime6)).
21811 */
21812axiom(not(happens(move(Move_Ret), Maptime6)),
21813   
21814    [ not(happens(run(Move_Ret), Maptime6)),
21815      not(happens(drive(Move_Ret), Maptime6))
21816    ]).
21817
21818% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6911
21819% xor Run, Drive
21820% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6912
21821xor([run,drive]).
21822
21823
21824% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6913
21825% [agent,time]
21826 % Initiates(Run(agent),Tired(agent),time).
21827axiom(initiates(run(Agent), tired(Agent), Time),
21828    []).
21829
21830% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6915
21831% agent James
21832% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6916
21833==> t(agent,james).
21834
21835
21836% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6917
21837% !HoldsAt(Tired(James),0).
21838 %  not(initially(tired(james))).
21839axiom(not(initially(tired(james))),
21840    []).
21841
21842
21843% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6918
21844% Happens(Move(James),0).
21845axiom(happens(move(james), t),
21846    [is_time(0)]).
21847
21848
21849% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6919
21850% HoldsAt(Tired(James),1).
21851holds_at(tired(james),1).
21852
21853% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6921
21854% range time 0 1
21855% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6922
21856==> range(time,0,1).
21857
21858% range offset 1 1
21859% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6923
21860==> range(offset,1,1).
21861%; End of file.
21862%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21863%; FILE: examples/Mueller2004b/TV1.e
21864%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
21865%;
21866%; Copyright (c) 2005 IBM Corporation and others.
21867%; All rights reserved. This program and the accompanying materials
21868%; are made available under the terms of the Common Public License v1.0
21869%; which accompanies this distribution, and is available at
21870%; http://www.eclipse.org/legal/cpl-v10.html
21871%;
21872%; Contributors:
21873%; IBM - Initial implementation
21874%;
21875%; @inproceedings{Mueller:2004b,
21876%;   author = "Erik T. Mueller",
21877%;   year = "2004",
21878%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
21879%;   editor = "Valerie Barr and Zdravko Markov",
21880%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
21881%;   pages = "147--152",
21882%;   address = "Menlo Park, CA",
21883%;   publisher = "AAAI Press",
21884%; }
21885%;
21886
21887% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6953
21888% load foundations/Root.e
21889
21890% load foundations/EC.e
21891
21892% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6956
21893% sort agent
21894% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6957
21895==> sort(agent).
21896
21897% sort switch
21898% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6958
21899==> sort(switch).
21900
21901% sort tv
21902% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6959
21903==> sort(tv).
21904
21905% function TVOf(switch): tv
21906 %  functional_predicate(tVOf(switch,tv)).
21907% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6961
21908==> mpred_prop(tVOf(switch,tv),functional_predicate).
21909==> meta_argtypes(tVOf(switch,tv)).
21910resultIsa(tVOf,tv).
21911
21912% fluent SwitchOn(switch)
21913 %  fluent(switchOn(switch)).
21914% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6962
21915==> mpred_prop(switchOn(switch),fluent).
21916==> meta_argtypes(switchOn(switch)).
21917
21918% fluent TVOn(tv)
21919 %  fluent(tVOn(tv)).
21920% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6963
21921==> mpred_prop(tVOn(tv),fluent).
21922==> meta_argtypes(tVOn(tv)).
21923
21924% fluent PluggedIn(tv)
21925 %  fluent(pluggedIn(tv)).
21926% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6964
21927==> mpred_prop(pluggedIn(tv),fluent).
21928==> meta_argtypes(pluggedIn(tv)).
21929
21930% event TurnOn(agent,switch)
21931 %  event(turnOn(agent,switch)).
21932% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6965
21933==> mpred_prop(turnOn(agent,switch),event).
21934==> meta_argtypes(turnOn(agent,switch)).
21935
21936% event TurnOff(agent,switch)
21937 %  event(turnOff(agent,switch)).
21938% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6966
21939==> mpred_prop(turnOff(agent,switch),event).
21940==> meta_argtypes(turnOff(agent,switch)).
21941
21942
21943% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6967
21944% [agent,switch,time]
21945 % Initiates(TurnOn(agent,switch),SwitchOn(switch),time).
21946axiom(initiates(turnOn(Agent, Switch), switchOn(Switch), Time),
21947    []).
21948
21949
21950% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6969
21951% [agent,switch,tv,time]
21952% TVOf(switch)=tv & HoldsAt(PluggedIn(tv),time) ->
21953% Initiates(TurnOn(agent,switch),TVOn(tv),time).
21954% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6971
21955axiom(initiates(turnOn(Agent, Switch), tVOn(Tv), Time),
21956   
21957    [ equals(tVOf(Switch), Tv),
21958      holds_at(pluggedIn(Tv), Time)
21959    ]).
21960
21961% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6973
21962% agent James
21963% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6974
21964==> t(agent,james).
21965
21966% switch Switch1
21967% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6975
21968==> t(switch,switch1).
21969
21970% tv TV1
21971% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6976
21972==> t(tv,tv1).
21973
21974
21975% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6977
21976% TVOf(Switch1)=TV1.
21977tVOf(switch1,tv1).
21978
21979
21980% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6978
21981% HoldsAt(PluggedIn(TV1),0).
21982axiom(initially(pluggedIn(tv1)),
21983    []).
21984
21985
21986% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6979
21987% !HoldsAt(SwitchOn(Switch1),0).
21988 %  not(initially(switchOn(switch1))).
21989axiom(not(initially(switchOn(switch1))),
21990    []).
21991
21992
21993% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6980
21994% !HoldsAt(TVOn(TV1),0).
21995 %  not(initially(tVOn(tv1))).
21996axiom(not(initially(tVOn(tv1))),
21997    []).
21998
21999
22000% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6981
22001% Happens(TurnOn(James,Switch1),0).
22002axiom(happens(turnOn(james, switch1), t),
22003    [is_time(0)]).
22004
22005% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6983
22006% range time 0 1
22007% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6984
22008==> range(time,0,1).
22009
22010% range offset 1 1
22011% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:6985
22012==> range(offset,1,1).
22013%; End of file.
22014%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
22015%; FILE: examples/Mueller2004b/RouletteWheel.e
22016%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
22017%;
22018%; Copyright (c) 2005 IBM Corporation and others.
22019%; All rights reserved. This program and the accompanying materials
22020%; are made available under the terms of the Common Public License v1.0
22021%; which accompanies this distribution, and is available at
22022%; http://www.eclipse.org/legal/cpl-v10.html
22023%;
22024%; Contributors:
22025%; IBM - Initial implementation
22026%;
22027%; @inproceedings{Mueller:2004b,
22028%;   author = "Erik T. Mueller",
22029%;   year = "2004",
22030%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
22031%;   editor = "Valerie Barr and Zdravko Markov",
22032%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
22033%;   pages = "147--152",
22034%;   address = "Menlo Park, CA",
22035%;   publisher = "AAAI Press",
22036%; }
22037%;
22038
22039% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7015
22040% load foundations/Root.e
22041
22042% load foundations/EC.e
22043
22044% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7018
22045% sort wheel
22046% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7019
22047==> sort(wheel).
22048
22049% sort value: integer
22050% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7020
22051==> subsort(value,integer).
22052
22053% fluent WheelValueDeterminingFluent(wheel,value)
22054 %  fluent(wheelValueDeterminingFluent(wheel,value)).
22055% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7022
22056==> mpred_prop(wheelValueDeterminingFluent(wheel,value),fluent).
22057==> meta_argtypes(wheelValueDeterminingFluent(wheel,value)).
22058
22059% fluent WheelValue(wheel,value)
22060 %  fluent(wheelValue(wheel,value)).
22061% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7023
22062==> mpred_prop(wheelValue(wheel,value),fluent).
22063==> meta_argtypes(wheelValue(wheel,value)).
22064
22065% noninertial WheelValueDeterminingFluent
22066% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7024
22067==> noninertial(wheelValueDeterminingFluent).
22068
22069% event Spin(wheel)
22070 %  event(spin(wheel)).
22071% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7025
22072==> mpred_prop(spin(wheel),event).
22073==> meta_argtypes(spin(wheel)).
22074
22075
22076% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7026
22077% [wheel,value1,value2,time]
22078% HoldsAt(WheelValue(wheel,value1),time) &
22079% HoldsAt(WheelValue(wheel,value2),time) ->
22080% value1=value2.
22081% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7029
22082axiom(Value1=Value2,
22083   
22084    [ holds_at(wheelValue(Wheel, Value1), Time),
22085      holds_at(wheelValue(Wheel, Value2), Time)
22086    ]).
22087
22088
22089% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7031
22090% [wheel,value1,value2,time]
22091% HoldsAt(WheelValueDeterminingFluent(wheel,value1),time) &
22092% HoldsAt(WheelValueDeterminingFluent(wheel,value2),time) ->
22093% value1=value2.
22094% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7034
22095axiom(Value1=Value2,
22096   
22097    [ holds_at(wheelValueDeterminingFluent(Wheel, Value1),
22098               Time),
22099      holds_at(wheelValueDeterminingFluent(Wheel, Value2),
22100               Time)
22101    ]).
22102
22103
22104% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7036
22105% [wheel,value,time]
22106% HoldsAt(WheelValueDeterminingFluent(wheel,value),time) ->
22107% Initiates(Spin(wheel),WheelValue(wheel,value),time).
22108% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7038
22109axiom(initiates(spin(Wheel), wheelValue(Wheel, Value), Time),
22110   
22111    [ holds_at(wheelValueDeterminingFluent(Wheel, Value),
22112               Time)
22113    ]).
22114
22115
22116% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7040
22117% [wheel,value1,value2,time]
22118% HoldsAt(WheelValue(wheel,value1),time) &
22119% HoldsAt(WheelValueDeterminingFluent(wheel,value2),time) &
22120% value1!=value2 ->
22121% Terminates(Spin(wheel),WheelValue(wheel,value1),time).
22122% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7044
22123axiom(terminates(spin(Wheel), wheelValue(Wheel, Value1), Time),
22124   
22125    [ holds_at(wheelValue(Wheel, Value1), Time),
22126      holds_at(wheelValueDeterminingFluent(Wheel, Value2),
22127               Time),
22128      { dif(Value1, Value2)
22129      }
22130    ]).
22131
22132
22133% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7046
22134% [wheel,time]
22135% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7047
22136% {value} % HoldsAt(WheelValueDeterminingFluent(wheel,value),time).
22137
22138 /*  exists([Value],
22139          holds_at(wheelValueDeterminingFluent(Wheel,Value),
22140   		Time)).
22141 */
22142
22143 /*  holds_at(wheelValueDeterminingFluent(WheelValueDeterminingFluent_Param, Some_Param), Time4) :-
22144       some(Some_Param,
22145            '$kolem_Fn_363'(WheelValueDeterminingFluent_Param, Time4)).
22146 */
22147axiom(holds_at(wheelValueDeterminingFluent(WheelValueDeterminingFluent_Param, Some_Param), Time4),
22148   
22149    [ some(Some_Param,
22150           '$kolem_Fn_363'(WheelValueDeterminingFluent_Param, Time4))
22151    ]).
22152
22153 /*  not(some(Some_Param8, '$kolem_Fn_363'(Fn_363_Param, Time7))) :-
22154       not(holds_at(wheelValueDeterminingFluent(Fn_363_Param,
22155                                                Some_Param8),
22156                    Time7)).
22157 */
22158axiom(not(some(Some_Param8, '$kolem_Fn_363'(Fn_363_Param, Time7))),
22159   
22160    [ not(holds_at(wheelValueDeterminingFluent(Fn_363_Param,
22161                                               Some_Param8),
22162                   Time7))
22163    ]).
22164
22165% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7049
22166% wheel Wheel
22167% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7050
22168==> t(wheel,wheel).
22169
22170
22171% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7051
22172% HoldsAt(WheelValue(Wheel,7),0).
22173axiom(initially(wheelValue(wheel, 7)),
22174    []).
22175
22176
22177% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7052
22178% Happens(Spin(Wheel),0).
22179axiom(happens(spin(wheel), t),
22180    [is_time(0)]).
22181
22182
22183% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7053
22184% HoldsAt(WheelValueDeterminingFluent(Wheel,7),1).
22185holds_at(wheelValueDeterminingFluent(wheel,7),1).
22186
22187% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7055
22188% completion Happens
22189% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7056
22190==> completion(happens).
22191
22192% range value 7 10
22193% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7058
22194==> range(value,7,10).
22195
22196% range time 0 1
22197% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7059
22198==> range(time,0,1).
22199
22200% range offset 1 1
22201% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7060
22202==> range(offset,1,1).
22203%; End of file.
22204%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
22205%; FILE: examples/Mueller2004b/PickUp.e
22206%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
22207%;
22208%; Copyright (c) 2005 IBM Corporation and others.
22209%; All rights reserved. This program and the accompanying materials
22210%; are made available under the terms of the Common Public License v1.0
22211%; which accompanies this distribution, and is available at
22212%; http://www.eclipse.org/legal/cpl-v10.html
22213%;
22214%; Contributors:
22215%; IBM - Initial implementation
22216%;
22217%; @inproceedings{Mueller:2004b,
22218%;   author = "Erik T. Mueller",
22219%;   year = "2004",
22220%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
22221%;   editor = "Valerie Barr and Zdravko Markov",
22222%;   booktitle = "\uppercase{P}roceedings of the \uppercase{S}eventeenth \uppercase{I}nternational \uppercase{F}lorida \uppercase{A}rtificial \uppercase{I}ntelligence \uppercase{R}esearch \uppercase{S}ociety \uppercase{C}onference",
22223%;   pages = "147--152",
22224%;   address = "Menlo Park, CA",
22225%;   publisher = "AAAI Press",
22226%; }
22227%;
22228
22229% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7090
22230% load foundations/Root.e
22231
22232% load foundations/EC.e
22233
22234% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7093
22235% sort object
22236% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7094
22237==> sort(object).
22238
22239% sort agent: object
22240% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7095
22241==> subsort(agent,object).
22242
22243% sort physobj: object
22244% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7096
22245==> subsort(physobj,object).
22246
22247% sort location
22248% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7097
22249==> sort(location).
22250
22251% fluent At(object,location)
22252 %  fluent(at(object,location)).
22253% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7099
22254==> mpred_prop(at(object,location),fluent).
22255==> meta_argtypes(at(object,location)).
22256
22257% fluent Holding(agent,physobj)
22258 %  fluent(holding(agent,physobj)).
22259% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7100
22260==> mpred_prop(holding(agent,physobj),fluent).
22261==> meta_argtypes(holding(agent,physobj)).
22262
22263% event PickUp(agent,physobj)
22264 %  event(pickUp(agent,physobj)).
22265% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7101
22266==> mpred_prop(pickUp(agent,physobj),event).
22267==> meta_argtypes(pickUp(agent,physobj)).
22268
22269% event SetDown(agent,physobj)
22270 %  event(setDown(agent,physobj)).
22271% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7102
22272==> mpred_prop(setDown(agent,physobj),event).
22273==> meta_argtypes(setDown(agent,physobj)).
22274
22275% event Move(agent,location,location)
22276 %  event(move(agent,location,location)).
22277% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7103
22278==> mpred_prop(move(agent,location,location),event).
22279==> meta_argtypes(move(agent,location,location)).
22280
22281
22282% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7104
22283%; state constraints
22284% [agent,location,physobj,time]
22285% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7107
22286% HoldsAt(At(agent,location),time) &
22287% HoldsAt(Holding(agent,physobj),time) ->
22288% HoldsAt(At(physobj,location),time).
22289% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7109
22290axiom(holds_at(at(Physobj, Location), Time),
22291   
22292    [ holds_at(at(Agent, Location), Time),
22293      holds_at(holding(Agent, Physobj), Time)
22294    ]).
22295
22296
22297% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7111
22298% [object,location1,location2,time]
22299% HoldsAt(At(object,location1),time) &
22300% HoldsAt(At(object,location2),time) ->
22301% location1=location2.
22302% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7114
22303axiom(Location1=Location2,
22304   
22305    [ holds_at(at(Object, Location1), Time),
22306      holds_at(at(Object, Location2), Time)
22307    ]).
22308
22309
22310% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7116
22311%; effect axioms
22312% [agent,location1,location2,time]
22313% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7119
22314% Initiates(Move(agent,location1,location2),At(agent,location2),time).
22315axiom(initiates(move(Agent, Location1, Location2), at(Agent, Location2), Time),
22316    []).
22317
22318
22319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7121
22320% [agent,location1,location2,time]
22321% Terminates(Move(agent,location1,location2),At(agent,location1),time).
22322% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7122
22323axiom(terminates(move(Agent, Location1, Location2), at(Agent, Location1), Time),
22324    []).
22325
22326
22327% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7124
22328% [agent,physobj,time]
22329% Initiates(PickUp(agent,physobj),Holding(agent,physobj),time).
22330% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7125
22331axiom(initiates(pickUp(Agent, Physobj), holding(Agent, Physobj), Time),
22332    []).
22333
22334
22335% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7127
22336% [agent,physobj,time]
22337% Terminates(SetDown(agent,physobj),Holding(agent,physobj),time).
22338% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7128
22339axiom(terminates(setDown(Agent, Physobj), holding(Agent, Physobj), Time),
22340    []).
22341
22342
22343% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7130
22344%; preconditions
22345% [agent,location1,location2,time]
22346% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7133
22347% Happens(Move(agent,location1,location2),time) ->
22348% HoldsAt(At(agent,location1),time).
22349% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7134
22350axiom(requires(move(Agent, Location1, Location2), Time),
22351    [holds_at(at(Agent, Location1), Time)]).
22352
22353
22354% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7136
22355% [agent,physobj,time]
22356% Happens(PickUp(agent,physobj),time) ->
22357% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7138
22358% {location}%  HoldsAt(At(agent,location),time) &
22359%            HoldsAt(At(physobj,location),time).
22360
22361 /*   exists([Location],
22362             if(happens(pickUp(Agent, Physobj), Time),
22363                 (holds_at(at(Agent, Location), Time), holds_at(at(Physobj, Location), Time)))).
22364 */
22365
22366 /*  not(some(Location6, '$kolem_Fn_364'(Fn_364_Param, At_Param, Maptime))) :-
22367       happens(pickUp(Fn_364_Param, At_Param), Maptime),
22368       (   not(holds_at(at(Fn_364_Param, Location6), Maptime))
22369       ;   not(holds_at(at(At_Param, Location6), Maptime))
22370       ).
22371 */
22372% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7139
22373axiom(not(some(Location6, '$kolem_Fn_364'(Fn_364_Param, At_Param, Maptime))),
22374   
22375    [ not(holds_at(at(Fn_364_Param, Location6), Maptime)),
22376      happens(pickUp(Fn_364_Param, At_Param), Maptime)
22377    ]).
22378axiom(not(some(Location6, '$kolem_Fn_364'(Fn_364_Param, At_Param, Maptime))),
22379   
22380    [ not(holds_at(at(At_Param, Location6), Maptime)),
22381      happens(pickUp(Fn_364_Param, At_Param), Maptime)
22382    ]).
22383
22384 /*  not(happens(pickUp(PickUp_Param, At_Param12), Maptime9)) :-
22385       (   not(holds_at(at(PickUp_Param, Location10), Maptime9))
22386       ;   not(holds_at(at(At_Param12, Location10), Maptime9))
22387       ),
22388       some(Location10,
22389            '$kolem_Fn_364'(PickUp_Param, At_Param12, Maptime9)).
22390 */
22391axiom(not(happens(pickUp(PickUp_Param, At_Param12), Maptime9)),
22392   
22393    [ not(holds_at(at(PickUp_Param, Location10), Maptime9)),
22394      some(Location10,
22395           '$kolem_Fn_364'(PickUp_Param, At_Param12, Maptime9))
22396    ]).
22397axiom(not(happens(pickUp(PickUp_Param, At_Param12), Maptime9)),
22398   
22399    [ not(holds_at(at(At_Param12, Location10), Maptime9)),
22400      some(Location10,
22401           '$kolem_Fn_364'(PickUp_Param, At_Param12, Maptime9))
22402    ]).
22403
22404 /*  holds_at(at(At_Param15, Location13), Time14) :-
22405       happens(pickUp(At_Param15, PickUp_Ret), Time14),
22406       some(Location13,
22407            '$kolem_Fn_364'(At_Param15, PickUp_Ret, Time14)).
22408 */
22409axiom(holds_at(at(At_Param15, Location13), Time14),
22410   
22411    [ happens(pickUp(At_Param15, PickUp_Ret), Time14),
22412      some(Location13,
22413           '$kolem_Fn_364'(At_Param15, PickUp_Ret, Time14))
22414    ]).
22415
22416 /*  holds_at(at(At_Param19, Location17), Time18) :-
22417       happens(pickUp(PickUp_Param20, At_Param19), Time18),
22418       some(Location17,
22419            '$kolem_Fn_364'(PickUp_Param20, At_Param19, Time18)).
22420 */
22421axiom(holds_at(at(At_Param19, Location17), Time18),
22422   
22423    [ happens(pickUp(PickUp_Param20, At_Param19), Time18),
22424      some(Location17,
22425           '$kolem_Fn_364'(PickUp_Param20, At_Param19, Time18))
22426    ]).
22427
22428
22429% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7141
22430%; releases
22431% [agent,physobj,location,time]
22432% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7144
22433% Releases(PickUp(agent,physobj),At(physobj,location),time).
22434axiom(releases(pickUp(Agent, Physobj), at(Physobj, Location), Time),
22435    []).
22436
22437
22438% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7146
22439% [agent,physobj,location,time]
22440% HoldsAt(At(agent,location),time) ->
22441% Initiates(SetDown(agent,physobj),At(physobj,location),time).
22442% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7148
22443axiom(initiates(setDown(Agent, Physobj), at(Physobj, Location), Time),
22444    [holds_at(at(Agent, Location), Time)]).
22445
22446
22447% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7150
22448%;[agent,physobj,location1,location2,time]
22449%;HoldsAt(At(agent,location1),time) &
22450%;location1 != location2 ->
22451%;Terminates(SetDown(agent,physobj),At(physobj,location2),time).
22452
22453% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7155
22454% agent James
22455% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7156
22456==> t(agent,james).
22457
22458% physobj Coin
22459% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7157
22460==> t(physobj,coin).
22461
22462% location L1, L2, L3, L4
22463% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7158
22464==> t(location,l1).
22465==> t(location,l2).
22466==> t(location,l3).
22467==> t(location,l4).
22468
22469
22470% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7159
22471% !HoldsAt(Holding(James,Coin),0).
22472 %  not(initially(holding(james,coin))).
22473axiom(not(initially(holding(james, coin))),
22474    []).
22475
22476
22477% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7160
22478% HoldsAt(At(Coin,L4),0).
22479axiom(initially(at(coin, l4)),
22480    []).
22481
22482
22483% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7161
22484% HoldsAt(At(James,L1),0).
22485axiom(initially(at(james, l1)),
22486    []).
22487
22488
22489% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7162
22490% Happens(Move(James,L1,L2),0).
22491axiom(happens(move(james, l1, l2), t),
22492    [is_time(0)]).
22493
22494
22495% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7163
22496% Happens(Move(James,L2,L3),1).
22497axiom(happens(move(james, l2, l3), start),
22498    [is_time(1), b(t, start), ignore(t+1=start)]).
22499
22500
22501% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7164
22502% Happens(Move(James,L3,L4),2).
22503axiom(happens(move(james, l3, l4), t2),
22504    [is_time(2), b(t, t2), ignore(t+2=t2)]).
22505
22506
22507% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7165
22508% Happens(PickUp(James,Coin),3).
22509axiom(happens(pickUp(james, coin), t3),
22510    [is_time(3), b(t, t3), ignore(t+3=t3)]).
22511
22512
22513% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7166
22514% Happens(Move(James,L4,L3),4).
22515axiom(happens(move(james, l4, l3), t4),
22516    [is_time(4), b(t, t4), ignore(t+4=t4)]).
22517
22518
22519% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7167
22520% Happens(Move(James,L3,L2),5).
22521axiom(happens(move(james, l3, l2), t5),
22522    [is_time(5), b(t, t5), ignore(t+5=t5)]).
22523
22524
22525% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7168
22526% Happens(SetDown(James,Coin),6).
22527axiom(happens(setDown(james, coin), t6),
22528    [is_time(6), b(t, t6), ignore(t+6=t6)]).
22529
22530
22531% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7169
22532% Happens(Move(James,L2,L3),7).
22533axiom(happens(move(james, l2, l3), t7),
22534    [is_time(7), b(t, t7), ignore(t+7=t7)]).
22535
22536
22537% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7170
22538% Happens(Move(James,L3,L4),8).
22539axiom(happens(move(james, l3, l4), t8),
22540    [is_time(8), b(t, t8), ignore(t+8=t8)]).
22541
22542% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7172
22543% completion Happens
22544% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7173
22545==> completion(happens).
22546
22547% range time 0 9
22548% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7175
22549==> range(time,0,9).
22550
22551% range offset 1 1
22552% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7176
22553==> range(offset,1,1).
22554%; End of file.
22555%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
22556%; FILE: examples/FrankEtAl2003/Story1.e
22557%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
22558%;
22559%; Copyright (c) 2005 IBM Corporation and others.
22560%; All rights reserved. This program and the accompanying materials
22561%; are made available under the terms of the Common Public License v1.0
22562%; which accompanies this distribution, and is available at
22563%; http://www.eclipse.org/legal/cpl-v10.html
22564%;
22565%; Contributors:
22566%; IBM - Initial implementation
22567%;
22568%; @article{FrankEtAl:2003,
22569%;   author = "Stefan L. Frank and Mathieu Koppen and Leo G. M. Noordman and Wietske Vonk",
22570%;   year = "2003",
22571%;   title = "Modeling knowledge-based inferences in story comprehension",
22572%;   journal = "Cognitive Science",
22573%;   volume = "27",
22574%;   pages = "875--910",
22575%; }
22576%;
22577
22578% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7204
22579% option modeldiff on
22580% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7205
22581:- set_ec_option(modeldiff, on).22582
22583% load foundations/Root.e
22584
22585% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7207
22586% load foundations/EC.e
22587
22588% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7209
22589% sort agent
22590% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7210
22591==> sort(agent).
22592
22593% load examples/FrankEtAl2003/FrankEtAl.e
22594
22595% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7213
22596% agent Bob, Jilly
22597% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7214
22598==> t(agent,bob).
22599==> t(agent,jilly).
22600
22601
22602% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7215
22603% !HoldsAt(Raining(),0).
22604 %  not(initially(raining())).
22605axiom(not(initially(raining())),
22606    []).
22607
22608
22609% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7216
22610% !HoldsAt(SunShining(),0).
22611 %  not(initially(sunShining())).
22612axiom(not(initially(sunShining())),
22613    []).
22614
22615
22616% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7218
22617% (HoldsAt(PlaySoccer(Bob),1) & HoldsAt(PlaySoccer(Jilly),1)) |
22618% (HoldsAt(PlayHideAndSeek(Bob),1) & HoldsAt(PlayHideAndSeek(Jilly),1)) |
22619% (HoldsAt(PlayComputerGame(Bob),1) & HoldsAt(PlayComputerGame(Jilly),1)).
22620
22621 /*   (   holds_at(playSoccer(bob), 1),
22622          holds_at(playSoccer(jilly), 1)
22623      ;   holds_at(playHideAndSeek(bob), 1),
22624          holds_at(playHideAndSeek(jilly), 1)
22625      ;   holds_at(playComputerGame(bob), 1),
22626          holds_at(playComputerGame(jilly), 1)
22627      ).
22628 */
22629
22630 /*  holds_at(playSoccer(bob), 1) :-
22631       (   not(holds_at(playHideAndSeek(bob), 1))
22632       ;   not(holds_at(playHideAndSeek(jilly), 1))
22633       ),
22634       (   not(holds_at(playComputerGame(bob), 1))
22635       ;   not(holds_at(playComputerGame(jilly), 1))
22636       ).
22637 */
22638% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7220
22639axiom(holds_at(playSoccer(bob), start),
22640   
22641    [ not(holds_at(playComputerGame(bob), start)),
22642      not(holds_at(playHideAndSeek(bob), start)),
22643      b(t, start),
22644      ignore(t+1=start)
22645    ]).
22646axiom(holds_at(playSoccer(bob), start),
22647   
22648    [ not(holds_at(playComputerGame(jilly), start)),
22649      not(holds_at(playHideAndSeek(bob), start)),
22650      b(t, start),
22651      ignore(t+1=start)
22652    ]).
22653axiom(holds_at(playSoccer(bob), start),
22654   
22655    [ not(holds_at(playComputerGame(bob), start)),
22656      not(holds_at(playHideAndSeek(jilly), start)),
22657      b(t, start),
22658      ignore(t+1=start)
22659    ]).
22660axiom(holds_at(playSoccer(bob), start),
22661   
22662    [ not(holds_at(playComputerGame(jilly), start)),
22663      not(holds_at(playHideAndSeek(jilly), start)),
22664      b(t, start),
22665      ignore(t+1=start)
22666    ]).
22667
22668 /*  holds_at(playSoccer(jilly), 1) :-
22669       (   not(holds_at(playHideAndSeek(bob), 1))
22670       ;   not(holds_at(playHideAndSeek(jilly), 1))
22671       ),
22672       (   not(holds_at(playComputerGame(bob), 1))
22673       ;   not(holds_at(playComputerGame(jilly), 1))
22674       ).
22675 */
22676axiom(holds_at(playSoccer(jilly), start),
22677   
22678    [ not(holds_at(playComputerGame(bob), start)),
22679      not(holds_at(playHideAndSeek(bob), start)),
22680      b(t, start),
22681      ignore(t+1=start)
22682    ]).
22683axiom(holds_at(playSoccer(jilly), start),
22684   
22685    [ not(holds_at(playComputerGame(jilly), start)),
22686      not(holds_at(playHideAndSeek(bob), start)),
22687      b(t, start),
22688      ignore(t+1=start)
22689    ]).
22690axiom(holds_at(playSoccer(jilly), start),
22691   
22692    [ not(holds_at(playComputerGame(bob), start)),
22693      not(holds_at(playHideAndSeek(jilly), start)),
22694      b(t, start),
22695      ignore(t+1=start)
22696    ]).
22697axiom(holds_at(playSoccer(jilly), start),
22698   
22699    [ not(holds_at(playComputerGame(jilly), start)),
22700      not(holds_at(playHideAndSeek(jilly), start)),
22701      b(t, start),
22702      ignore(t+1=start)
22703    ]).
22704
22705 /*  holds_at(playHideAndSeek(bob), 1) :-
22706       (   not(holds_at(playComputerGame(bob), 1))
22707       ;   not(holds_at(playComputerGame(jilly), 1))
22708       ),
22709       (   not(holds_at(playSoccer(bob), 1))
22710       ;   not(holds_at(playSoccer(jilly), 1))
22711       ).
22712 */
22713axiom(holds_at(playHideAndSeek(bob), start),
22714   
22715    [ not(holds_at(playSoccer(bob), start)),
22716      not(holds_at(playComputerGame(bob), start)),
22717      b(t, start),
22718      ignore(t+1=start)
22719    ]).
22720axiom(holds_at(playHideAndSeek(bob), start),
22721   
22722    [ not(holds_at(playSoccer(jilly), start)),
22723      not(holds_at(playComputerGame(bob), start)),
22724      b(t, start),
22725      ignore(t+1=start)
22726    ]).
22727axiom(holds_at(playHideAndSeek(bob), start),
22728   
22729    [ not(holds_at(playSoccer(bob), start)),
22730      not(holds_at(playComputerGame(jilly), start)),
22731      b(t, start),
22732      ignore(t+1=start)
22733    ]).
22734axiom(holds_at(playHideAndSeek(bob), start),
22735   
22736    [ not(holds_at(playSoccer(jilly), start)),
22737      not(holds_at(playComputerGame(jilly), start)),
22738      b(t, start),
22739      ignore(t+1=start)
22740    ]).
22741
22742 /*  holds_at(playHideAndSeek(jilly), 1) :-
22743       (   not(holds_at(playComputerGame(bob), 1))
22744       ;   not(holds_at(playComputerGame(jilly), 1))
22745       ),
22746       (   not(holds_at(playSoccer(bob), 1))
22747       ;   not(holds_at(playSoccer(jilly), 1))
22748       ).
22749 */
22750axiom(holds_at(playHideAndSeek(jilly), start),
22751   
22752    [ not(holds_at(playSoccer(bob), start)),
22753      not(holds_at(playComputerGame(bob), start)),
22754      b(t, start),
22755      ignore(t+1=start)
22756    ]).
22757axiom(holds_at(playHideAndSeek(jilly), start),
22758   
22759    [ not(holds_at(playSoccer(jilly), start)),
22760      not(holds_at(playComputerGame(bob), start)),
22761      b(t, start),
22762      ignore(t+1=start)
22763    ]).
22764axiom(holds_at(playHideAndSeek(jilly), start),
22765   
22766    [ not(holds_at(playSoccer(bob), start)),
22767      not(holds_at(playComputerGame(jilly), start)),
22768      b(t, start),
22769      ignore(t+1=start)
22770    ]).
22771axiom(holds_at(playHideAndSeek(jilly), start),
22772   
22773    [ not(holds_at(playSoccer(jilly), start)),
22774      not(holds_at(playComputerGame(jilly), start)),
22775      b(t, start),
22776      ignore(t+1=start)
22777    ]).
22778
22779 /*  holds_at(playComputerGame(bob), 1) :-
22780       (   not(holds_at(playHideAndSeek(bob), 1))
22781       ;   not(holds_at(playHideAndSeek(jilly), 1))
22782       ),
22783       (   not(holds_at(playSoccer(bob), 1))
22784       ;   not(holds_at(playSoccer(jilly), 1))
22785       ).
22786 */
22787axiom(holds_at(playComputerGame(bob), start),
22788   
22789    [ not(holds_at(playSoccer(bob), start)),
22790      not(holds_at(playHideAndSeek(bob), start)),
22791      b(t, start),
22792      ignore(t+1=start)
22793    ]).
22794axiom(holds_at(playComputerGame(bob), start),
22795   
22796    [ not(holds_at(playSoccer(jilly), start)),
22797      not(holds_at(playHideAndSeek(bob), start)),
22798      b(t, start),
22799      ignore(t+1=start)
22800    ]).
22801axiom(holds_at(playComputerGame(bob), start),
22802   
22803    [ not(holds_at(playSoccer(bob), start)),
22804      not(holds_at(playHideAndSeek(jilly), start)),
22805      b(t, start),
22806      ignore(t+1=start)
22807    ]).
22808axiom(holds_at(playComputerGame(bob), start),
22809   
22810    [ not(holds_at(playSoccer(jilly), start)),
22811      not(holds_at(playHideAndSeek(jilly), start)),
22812      b(t, start),
22813      ignore(t+1=start)
22814    ]).
22815
22816 /*  holds_at(playComputerGame(jilly), 1) :-
22817       (   not(holds_at(playHideAndSeek(bob), 1))
22818       ;   not(holds_at(playHideAndSeek(jilly), 1))
22819       ),
22820       (   not(holds_at(playSoccer(bob), 1))
22821       ;   not(holds_at(playSoccer(jilly), 1))
22822       ).
22823 */
22824axiom(holds_at(playComputerGame(jilly), start),
22825   
22826    [ not(holds_at(playSoccer(bob), start)),
22827      not(holds_at(playHideAndSeek(bob), start)),
22828      b(t, start),
22829      ignore(t+1=start)
22830    ]).
22831axiom(holds_at(playComputerGame(jilly), start),
22832   
22833    [ not(holds_at(playSoccer(jilly), start)),
22834      not(holds_at(playHideAndSeek(bob), start)),
22835      b(t, start),
22836      ignore(t+1=start)
22837    ]).
22838axiom(holds_at(playComputerGame(jilly), start),
22839   
22840    [ not(holds_at(playSoccer(bob), start)),
22841      not(holds_at(playHideAndSeek(jilly), start)),
22842      b(t, start),
22843      ignore(t+1=start)
22844    ]).
22845axiom(holds_at(playComputerGame(jilly), start),
22846   
22847    [ not(holds_at(playSoccer(jilly), start)),
22848      not(holds_at(playHideAndSeek(jilly), start)),
22849      b(t, start),
22850      ignore(t+1=start)
22851    ]).
22852
22853
22854% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7222
22855% HoldsAt(Win(Bob),1) | HoldsAt(Win(Jilly),1).
22856
22857 /*   (   holds_at(win(bob), 1)
22858      ;   holds_at(win(jilly), 1)
22859      ).
22860 */
22861
22862 /*  holds_at(win(bob), 1) :-
22863       not(holds_at(win(jilly), 1)).
22864 */
22865axiom(holds_at(win(bob), start),
22866    [not(holds_at(win(jilly), start)), b(t, start), ignore(t+1=start)]).
22867
22868 /*  holds_at(win(jilly), 1) :-
22869       not(holds_at(win(bob), 1)).
22870 */
22871axiom(holds_at(win(jilly), start),
22872    [not(holds_at(win(bob), start)), b(t, start), ignore(t+1=start)]).
22873
22874% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7224
22875% range time 0 1
22876% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7225
22877==> range(time,0,1).
22878
22879% range offset 0 0
22880% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7226
22881==> range(offset,0,0).
22882%; End of file.
22883%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
22884%; FILE: examples/FrankEtAl2003/FrankEtAl.e
22885%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
22886%;
22887%; Copyright (c) 2005 IBM Corporation and others.
22888%; All rights reserved. This program and the accompanying materials
22889%; are made available under the terms of the Common Public License v1.0
22890%; which accompanies this distribution, and is available at
22891%; http://www.eclipse.org/legal/cpl-v10.html
22892%;
22893%; Contributors:
22894%; IBM - Initial implementation
22895%;
22896%; @article{FrankEtAl:2003,
22897%;   author = "Stefan L. Frank and Mathieu Koppen and Leo G. M. Noordman and Wietske Vonk",
22898%;   year = "2003",
22899%;   title = "Modeling knowledge-based inferences in story comprehension",
22900%;   journal = "Cognitive Science",
22901%;   volume = "27",
22902%;   pages = "875--910",
22903%; }
22904%;
22905
22906% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7254
22907% fluent SunShining()
22908 %  fluent(sunShining()).
22909% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7255
22910==> mpred_prop(sunShining(),fluent).
22911==> meta_argtypes(sunShining()).
22912
22913% fluent Raining()
22914 %  fluent(raining()).
22915% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7256
22916==> mpred_prop(raining(),fluent).
22917==> meta_argtypes(raining()).
22918
22919% fluent Outside(agent)
22920 %  fluent(outside(agent)).
22921% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7257
22922==> mpred_prop(outside(agent),fluent).
22923==> meta_argtypes(outside(agent)).
22924
22925% fluent PlaySoccer(agent)
22926 %  fluent(playSoccer(agent)).
22927% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7258
22928==> mpred_prop(playSoccer(agent),fluent).
22929==> meta_argtypes(playSoccer(agent)).
22930
22931% fluent PlayHideAndSeek(agent)
22932 %  fluent(playHideAndSeek(agent)).
22933% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7259
22934==> mpred_prop(playHideAndSeek(agent),fluent).
22935==> meta_argtypes(playHideAndSeek(agent)).
22936
22937% fluent PlayComputerGame(agent)
22938 %  fluent(playComputerGame(agent)).
22939% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7260
22940==> mpred_prop(playComputerGame(agent),fluent).
22941==> meta_argtypes(playComputerGame(agent)).
22942
22943% fluent PlayWithDog(agent)
22944 %  fluent(playWithDog(agent)).
22945% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7261
22946==> mpred_prop(playWithDog(agent),fluent).
22947==> meta_argtypes(playWithDog(agent)).
22948
22949% fluent Win(agent)
22950 %  fluent(win(agent)).
22951% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7262
22952==> mpred_prop(win(agent),fluent).
22953==> meta_argtypes(win(agent)).
22954
22955% noninertial Outside, PlaySoccer, PlayHideAndSeek, PlayComputerGame
22956% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7264
22957==> noninertial(outside).
22958==> noninertial(playSoccer).
22959==> noninertial(playHideAndSeek).
22960==> noninertial(playComputerGame).
22961
22962% noninertial PlayWithDog, Win
22963% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7265
22964==> noninertial(playWithDog).
22965==> noninertial(win).
22966
22967% xor PlaySoccer, PlayHideAndSeek, PlayComputerGame, PlayWithDog
22968% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7267
22969xor([playSoccer,playHideAndSeek,playComputerGame,playWithDog]).
22970
22971
22972% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7268
22973% [agent,time]
22974% HoldsAt(PlaySoccer(agent),time) ->
22975% HoldsAt(Outside(agent),time).
22976% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7270
22977axiom(holds_at(outside(Agent), Time),
22978    [holds_at(playSoccer(Agent), Time)]).
22979
22980
22981% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7272
22982% [agent,time]
22983% HoldsAt(PlaySoccer(agent),time) ->
22984% ({agent1} agent1!=agent & HoldsAt(PlaySoccer(agent1),time)).
22985
22986 /*   if(holds_at(playSoccer(Agent), Time),
22987         exists([Agent1],
22988                 (Agent1\=Agent, holds_at(playSoccer(Agent1), Time)))).
22989 */
22990
22991 /*  not(holds_at(playSoccer(PlaySoccer_Ret), Time3)) :-
22992       (   not({dif(Dif_Param, PlaySoccer_Ret)})
22993       ;   not(holds_at(playSoccer(Dif_Param), Time3))
22994       ).
22995 */
22996% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7274
22997axiom(not(holds_at(playSoccer(PlaySoccer_Ret), Time3)),
22998    [not({dif(Dif_Param, PlaySoccer_Ret)})]).
22999axiom(not(holds_at(playSoccer(PlaySoccer_Ret), Time3)),
23000    [not(holds_at(playSoccer(Dif_Param), Time3))]).
23001
23002 /*  { dif(Dif_Param7, Dif_Ret)
23003   } :-
23004       holds_at(playSoccer(Dif_Ret), Time6).
23005 */
23006axiom({ dif(Dif_Param7, Dif_Ret)
23007},
23008    [holds_at(playSoccer(Dif_Ret), Time6)]).
23009
23010
23011% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7276
23012% [agent,time]
23013% HoldsAt(PlayHideAndSeek(agent),time) ->
23014% ({agent1} agent1!=agent & HoldsAt(PlayHideAndSeek(agent1),time)).
23015
23016 /*   if(holds_at(playHideAndSeek(Agent), Time),
23017         exists([Agent1],
23018                 (Agent1\=Agent, holds_at(playHideAndSeek(Agent1), Time)))).
23019 */
23020
23021 /*  not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time3)) :-
23022       (   not({dif(Dif_Param, PlayHideAndSeek_Ret)})
23023       ;   not(holds_at(playHideAndSeek(Dif_Param), Time3))
23024       ).
23025 */
23026% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7278
23027axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time3)),
23028    [not({dif(Dif_Param, PlayHideAndSeek_Ret)})]).
23029axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time3)),
23030    [not(holds_at(playHideAndSeek(Dif_Param), Time3))]).
23031
23032 /*  { dif(Dif_Param7, Dif_Ret)
23033   } :-
23034       holds_at(playHideAndSeek(Dif_Ret), Time6).
23035 */
23036axiom({ dif(Dif_Param7, Dif_Ret)
23037},
23038    [holds_at(playHideAndSeek(Dif_Ret), Time6)]).
23039
23040
23041% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7280
23042% [agent,time]
23043% HoldsAt(PlayComputerGame(agent),time) ->
23044% !HoldsAt(Outside(agent),time).
23045% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7282
23046axiom(not(holds_at(outside(Agent), Time)),
23047    [holds_at(playComputerGame(Agent), Time)]).
23048
23049
23050% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7284
23051% [agent,time]
23052% HoldsAt(Win(agent),time) ->
23053% (HoldsAt(PlaySoccer(agent),time) |
23054%  HoldsAt(PlayHideAndSeek(agent),time) |
23055%  (HoldsAt(PlayComputerGame(agent),time) &
23056%   ({agent1} agent1!=agent & HoldsAt(PlayComputerGame(agent1),time)))).
23057
23058 /*   if(holds_at(win(Agent), Time),
23059          (holds_at(playSoccer(Agent), Time);holds_at(playHideAndSeek(Agent), Time);holds_at(playComputerGame(Agent), Time), exists([Agent1],  (Agent1\=Agent, holds_at(playComputerGame(Agent1), Time))))).
23060 */
23061
23062 /*  not(holds_at(win(Win_Ret), Time3)) :-
23063       not(holds_at(playSoccer(Win_Ret), Time3)),
23064       not(holds_at(playHideAndSeek(Win_Ret), Time3)),
23065       (   not(holds_at(playComputerGame(Win_Ret), Time3))
23066       ;   not({dif(Dif_Param, Win_Ret)})
23067       ;   not(holds_at(playComputerGame(Dif_Param), Time3))
23068       ).
23069 */
23070% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7289
23071axiom(not(holds_at(win(Win_Ret), Time3)),
23072   
23073    [ not(holds_at(playComputerGame(Win_Ret), Time3)),
23074      not(holds_at(playSoccer(Win_Ret), Time3)),
23075      not(holds_at(playHideAndSeek(Win_Ret), Time3))
23076    ]).
23077axiom(not(holds_at(win(Win_Ret), Time3)),
23078   
23079    [ not({dif(Dif_Param, Win_Ret)}),
23080      not(holds_at(playSoccer(Win_Ret), Time3)),
23081      not(holds_at(playHideAndSeek(Win_Ret), Time3))
23082    ]).
23083axiom(not(holds_at(win(Win_Ret), Time3)),
23084   
23085    [ not(holds_at(playComputerGame(Dif_Param), Time3)),
23086      not(holds_at(playSoccer(Win_Ret), Time3)),
23087      not(holds_at(playHideAndSeek(Win_Ret), Time3))
23088    ]).
23089
23090 /*  holds_at(playSoccer(PlaySoccer_Ret), Time6) :-
23091       ( not(holds_at(playHideAndSeek(PlaySoccer_Ret), Time6)),
23092         (   not(holds_at(playComputerGame(PlaySoccer_Ret), Time6))
23093         ;   not({dif(Dif_Param7, PlaySoccer_Ret)})
23094         ;   not(holds_at(playComputerGame(Dif_Param7), Time6))
23095         )
23096       ),
23097       holds_at(win(PlaySoccer_Ret), Time6).
23098 */
23099axiom(holds_at(playSoccer(PlaySoccer_Ret), Time6),
23100   
23101    [ not(holds_at(playComputerGame(PlaySoccer_Ret), Time6)),
23102      not(holds_at(playHideAndSeek(PlaySoccer_Ret), Time6)),
23103      holds_at(win(PlaySoccer_Ret), Time6)
23104    ]).
23105axiom(holds_at(playSoccer(PlaySoccer_Ret), Time6),
23106   
23107    [ not({dif(Dif_Param7, PlaySoccer_Ret)}),
23108      not(holds_at(playHideAndSeek(PlaySoccer_Ret), Time6)),
23109      holds_at(win(PlaySoccer_Ret), Time6)
23110    ]).
23111axiom(holds_at(playSoccer(PlaySoccer_Ret), Time6),
23112   
23113    [ not(holds_at(playComputerGame(Dif_Param7), Time6)),
23114      not(holds_at(playHideAndSeek(PlaySoccer_Ret), Time6)),
23115      holds_at(win(PlaySoccer_Ret), Time6)
23116    ]).
23117
23118 /*  holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time9) :-
23119       (   not(holds_at(playComputerGame(PlayHideAndSeek_Ret), Time9))
23120       ;   not({dif(Dif_Param10, PlayHideAndSeek_Ret)})
23121       ;   not(holds_at(playComputerGame(Dif_Param10), Time9))
23122       ),
23123       not(holds_at(playSoccer(PlayHideAndSeek_Ret), Time9)),
23124       holds_at(win(PlayHideAndSeek_Ret), Time9).
23125 */
23126axiom(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time9),
23127   
23128    [ not(holds_at(playComputerGame(PlayHideAndSeek_Ret), Time9)),
23129      not(holds_at(playSoccer(PlayHideAndSeek_Ret), Time9)),
23130      holds_at(win(PlayHideAndSeek_Ret), Time9)
23131    ]).
23132axiom(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time9),
23133   
23134    [ not({dif(Dif_Param10, PlayHideAndSeek_Ret)}),
23135      not(holds_at(playSoccer(PlayHideAndSeek_Ret), Time9)),
23136      holds_at(win(PlayHideAndSeek_Ret), Time9)
23137    ]).
23138axiom(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time9),
23139   
23140    [ not(holds_at(playComputerGame(Dif_Param10), Time9)),
23141      not(holds_at(playSoccer(PlayHideAndSeek_Ret), Time9)),
23142      holds_at(win(PlayHideAndSeek_Ret), Time9)
23143    ]).
23144
23145 /*  holds_at(playComputerGame(PlayComputerGame_Ret), Time12) :-
23146       not(holds_at(playHideAndSeek(PlayComputerGame_Ret), Time12)),
23147       not(holds_at(playSoccer(PlayComputerGame_Ret), Time12)),
23148       holds_at(win(PlayComputerGame_Ret), Time12).
23149 */
23150axiom(holds_at(playComputerGame(PlayComputerGame_Ret), Time12),
23151   
23152    [ not(holds_at(playHideAndSeek(PlayComputerGame_Ret), Time12)),
23153      not(holds_at(playSoccer(PlayComputerGame_Ret), Time12)),
23154      holds_at(win(PlayComputerGame_Ret), Time12)
23155    ]).
23156
23157 /*  { dif(Dif_Param15, Dif_Ret)
23158   } :-
23159       not(holds_at(playHideAndSeek(Dif_Ret), Time14)),
23160       not(holds_at(playSoccer(Dif_Ret), Time14)),
23161       holds_at(win(Dif_Ret), Time14).
23162 */
23163axiom({ dif(Dif_Param15, Dif_Ret)
23164},
23165   
23166    [ not(holds_at(playHideAndSeek(Dif_Ret), Time14)),
23167      not(holds_at(playSoccer(Dif_Ret), Time14)),
23168      holds_at(win(Dif_Ret), Time14)
23169    ]).
23170
23171 /*  holds_at(playComputerGame(PlayComputerGame_Ret18), Time17) :-
23172       not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret19), Time17)),
23173       not(holds_at(playSoccer(PlayHideAndSeek_Ret19), Time17)),
23174       holds_at(win(PlayHideAndSeek_Ret19), Time17).
23175 */
23176axiom(holds_at(playComputerGame(PlayComputerGame_Ret18), Time17),
23177   
23178    [ not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret19), Time17)),
23179      not(holds_at(playSoccer(PlayHideAndSeek_Ret19), Time17)),
23180      holds_at(win(PlayHideAndSeek_Ret19), Time17)
23181    ]).
23182
23183
23184% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7291
23185% [agent,time]
23186% HoldsAt(PlaySoccer(agent),time) &
23187% HoldsAt(Win(agent),time) ->
23188% !HoldsAt(PlaySoccer(agent),time+1).
23189% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7294
23190axiom(not(holds_at(playSoccer(Agent), start)),
23191   
23192    [ holds_at(playSoccer(Agent), t),
23193      holds_at(win(Agent), t),
23194      b(t, start),
23195      ignore(t+1=start)
23196    ]).
23197
23198
23199% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7296
23200% [agent,time]
23201% HoldsAt(PlayHideAndSeek(agent),time) &
23202% HoldsAt(Win(agent),time) ->
23203% !HoldsAt(PlayHideAndSeek(agent),time+1).
23204% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7299
23205axiom(not(holds_at(playHideAndSeek(Agent), start)),
23206   
23207    [ holds_at(playHideAndSeek(Agent), t),
23208      holds_at(win(Agent), t),
23209      b(t, start),
23210      ignore(t+1=start)
23211    ]).
23212
23213
23214% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7301
23215% [agent,time]
23216% HoldsAt(PlayComputerGame(agent),time) &
23217% HoldsAt(Win(agent),time) ->
23218% !HoldsAt(PlayComputerGame(agent),time+1).
23219% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7304
23220axiom(not(holds_at(playComputerGame(Agent), start)),
23221   
23222    [ holds_at(playComputerGame(Agent), t),
23223      holds_at(win(Agent), t),
23224      b(t, start),
23225      ignore(t+1=start)
23226    ]).
23227
23228
23229% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7306
23230% [agent,time]
23231% HoldsAt(Win(agent),time) ->
23232% HoldsAt(PlaySoccer(agent),time-1) |
23233% HoldsAt(PlayHideAndSeek(agent),time-1) |
23234% HoldsAt(PlayComputerGame(agent),time-1).
23235
23236 /*   if(holds_at(win(Agent), Time),
23237          (holds_at(playSoccer(Agent), Time-1);holds_at(playHideAndSeek(Agent), Time-1);holds_at(playComputerGame(Agent), Time-1))).
23238 */
23239
23240 /*  holds_at(playSoccer(PlaySoccer_Ret), Time2-1) :-
23241       ( not(holds_at(playHideAndSeek(PlaySoccer_Ret), Time2-1)),
23242         not(holds_at(playComputerGame(PlaySoccer_Ret), Time2-1))
23243       ),
23244       holds_at(win(PlaySoccer_Ret), Time2).
23245 */
23246% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7310
23247axiom(holds_at(playSoccer(PlaySoccer_Ret), t),
23248   
23249    [ not(holds_at(playHideAndSeek(PlaySoccer_Ret), t)),
23250      not(holds_at(playComputerGame(PlaySoccer_Ret), t)),
23251      holds_at(win(PlaySoccer_Ret), start),
23252      b(t, start),
23253      ignore(start-1=t)
23254    ]).
23255
23256 /*  holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time4-1) :-
23257       not(holds_at(playComputerGame(PlayHideAndSeek_Ret), Time4-1)),
23258       not(holds_at(playSoccer(PlayHideAndSeek_Ret), Time4-1)),
23259       holds_at(win(PlayHideAndSeek_Ret), Time4).
23260 */
23261axiom(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), t),
23262   
23263    [ not(holds_at(playComputerGame(PlayHideAndSeek_Ret), t)),
23264      not(holds_at(playSoccer(PlayHideAndSeek_Ret), t)),
23265      holds_at(win(PlayHideAndSeek_Ret), start),
23266      b(t, start),
23267      ignore(start-1=t)
23268    ]).
23269
23270 /*  holds_at(playComputerGame(PlayComputerGame_Ret), Time6-1) :-
23271       not(holds_at(playHideAndSeek(PlayComputerGame_Ret), Time6-1)),
23272       not(holds_at(playSoccer(PlayComputerGame_Ret), Time6-1)),
23273       holds_at(win(PlayComputerGame_Ret), Time6).
23274 */
23275axiom(holds_at(playComputerGame(PlayComputerGame_Ret), t),
23276   
23277    [ not(holds_at(playHideAndSeek(PlayComputerGame_Ret), t)),
23278      not(holds_at(playSoccer(PlayComputerGame_Ret), t)),
23279      holds_at(win(PlayComputerGame_Ret), start),
23280      b(t, start),
23281      ignore(start-1=t)
23282    ]).
23283
23284 /*  not(holds_at(win(Win_Ret), Time8)) :-
23285       not(holds_at(playSoccer(Win_Ret), Time8-1)),
23286       not(holds_at(playHideAndSeek(Win_Ret), Time8-1)),
23287       not(holds_at(playComputerGame(Win_Ret), Time8-1)).
23288 */
23289axiom(not(holds_at(win(Win_Ret), start)),
23290   
23291    [ not(holds_at(playSoccer(Win_Ret), t)),
23292      not(holds_at(playHideAndSeek(Win_Ret), t)),
23293      not(holds_at(playComputerGame(Win_Ret), t)),
23294      b(t, start),
23295      ignore(start-1=t)
23296    ]).
23297
23298
23299% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7312
23300% [agent,time]
23301% HoldsAt(PlaySoccer(agent),time) ->
23302% !HoldsAt(Raining(),time).
23303% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7314
23304axiom(not(holds_at(raining(), Time)),
23305    [holds_at(playSoccer(Agent), Time)]).
23306
23307
23308% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7316
23309% [agent,time]
23310% HoldsAt(Win(agent),time) ->
23311% !({agent1} agent1!=agent & HoldsAt(Win(agent1),time)).
23312% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7318
23313axiom(not(exists([Agent1],  (Agent1\=Agent, holds_at(win(Agent1), Time)))),
23314    [holds_at(win(Agent), Time)]).
23315
23316
23317% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7320
23318% [agent1,agent2,time]
23319% HoldsAt(PlayHideAndSeek(agent1),time) &
23320% HoldsAt(PlayHideAndSeek(agent2),time) ->
23321% ((HoldsAt(Outside(agent1),time) & HoldsAt(Outside(agent2),time)) |
23322%  (!HoldsAt(Outside(agent1),time) & !HoldsAt(Outside(agent2),time))).
23323
23324 /*   if((holds_at(playHideAndSeek(Agent1), Time), holds_at(playHideAndSeek(Agent2), Time)),
23325          (holds_at(outside(Agent1), Time), holds_at(outside(Agent2), Time);not(holds_at(outside(Agent1), Time)), not(holds_at(outside(Agent2), Time)))).
23326 */
23327
23328 /*  not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time3)) :-
23329       holds_at(playHideAndSeek(PlayHideAndSeek_Ret5), Time3),
23330       (   not(holds_at(outside(PlayHideAndSeek_Ret), Time3))
23331       ;   not(holds_at(outside(PlayHideAndSeek_Ret5), Time3))
23332       ),
23333       (   holds_at(outside(PlayHideAndSeek_Ret), Time3)
23334       ;   holds_at(outside(PlayHideAndSeek_Ret5), Time3)
23335       ).
23336 */
23337% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7324
23338axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time3)),
23339   
23340    [ holds_at(outside(PlayHideAndSeek_Ret), Time3),
23341      not(holds_at(outside(PlayHideAndSeek_Ret), Time3)),
23342      holds_at(playHideAndSeek(PlayHideAndSeek_Ret5), Time3)
23343    ]).
23344axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time3)),
23345   
23346    [ holds_at(outside(PlayHideAndSeek_Ret5), Time3),
23347      not(holds_at(outside(PlayHideAndSeek_Ret), Time3)),
23348      holds_at(playHideAndSeek(PlayHideAndSeek_Ret5), Time3)
23349    ]).
23350axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time3)),
23351   
23352    [ holds_at(outside(PlayHideAndSeek_Ret), Time3),
23353      not(holds_at(outside(PlayHideAndSeek_Ret5), Time3)),
23354      holds_at(playHideAndSeek(PlayHideAndSeek_Ret5), Time3)
23355    ]).
23356axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret), Time3)),
23357   
23358    [ holds_at(outside(PlayHideAndSeek_Ret5), Time3),
23359      not(holds_at(outside(PlayHideAndSeek_Ret5), Time3)),
23360      holds_at(playHideAndSeek(PlayHideAndSeek_Ret5), Time3)
23361    ]).
23362
23363 /*  not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret7), Time6)) :-
23364       holds_at(playHideAndSeek(PlayHideAndSeek_Ret8), Time6),
23365       (   not(holds_at(outside(PlayHideAndSeek_Ret8), Time6))
23366       ;   not(holds_at(outside(PlayHideAndSeek_Ret7), Time6))
23367       ),
23368       (   holds_at(outside(PlayHideAndSeek_Ret8), Time6)
23369       ;   holds_at(outside(PlayHideAndSeek_Ret7), Time6)
23370       ).
23371 */
23372axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret7), Time6)),
23373   
23374    [ holds_at(outside(PlayHideAndSeek_Ret8), Time6),
23375      not(holds_at(outside(PlayHideAndSeek_Ret8), Time6)),
23376      holds_at(playHideAndSeek(PlayHideAndSeek_Ret8), Time6)
23377    ]).
23378axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret7), Time6)),
23379   
23380    [ holds_at(outside(PlayHideAndSeek_Ret7), Time6),
23381      not(holds_at(outside(PlayHideAndSeek_Ret8), Time6)),
23382      holds_at(playHideAndSeek(PlayHideAndSeek_Ret8), Time6)
23383    ]).
23384axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret7), Time6)),
23385   
23386    [ holds_at(outside(PlayHideAndSeek_Ret8), Time6),
23387      not(holds_at(outside(PlayHideAndSeek_Ret7), Time6)),
23388      holds_at(playHideAndSeek(PlayHideAndSeek_Ret8), Time6)
23389    ]).
23390axiom(not(holds_at(playHideAndSeek(PlayHideAndSeek_Ret7), Time6)),
23391   
23392    [ holds_at(outside(PlayHideAndSeek_Ret7), Time6),
23393      not(holds_at(outside(PlayHideAndSeek_Ret7), Time6)),
23394      holds_at(playHideAndSeek(PlayHideAndSeek_Ret8), Time6)
23395    ]).
23396
23397 /*  holds_at(outside(Outside_Ret), Time9) :-
23398       (   holds_at(outside(Outside_Ret), Time9)
23399       ;   holds_at(outside(Outside_Ret11), Time9)
23400       ),
23401       holds_at(playHideAndSeek(Outside_Ret), Time9),
23402       holds_at(playHideAndSeek(Outside_Ret11), Time9).
23403 */
23404axiom(holds_at(outside(Outside_Ret), Time9),
23405   
23406    [ holds_at(outside(Outside_Ret), Time9),
23407      holds_at(playHideAndSeek(Outside_Ret), Time9),
23408      holds_at(playHideAndSeek(Outside_Ret11), Time9)
23409    ]).
23410axiom(holds_at(outside(Outside_Ret), Time9),
23411   
23412    [ holds_at(outside(Outside_Ret11), Time9),
23413      holds_at(playHideAndSeek(Outside_Ret), Time9),
23414      holds_at(playHideAndSeek(Outside_Ret11), Time9)
23415    ]).
23416
23417 /*  holds_at(outside(Outside_Ret13), Time12) :-
23418       (   holds_at(outside(Outside_Ret14), Time12)
23419       ;   holds_at(outside(Outside_Ret13), Time12)
23420       ),
23421       holds_at(playHideAndSeek(Outside_Ret14), Time12),
23422       holds_at(playHideAndSeek(Outside_Ret13), Time12).
23423 */
23424axiom(holds_at(outside(Outside_Ret13), Time12),
23425   
23426    [ holds_at(outside(Outside_Ret14), Time12),
23427      holds_at(playHideAndSeek(Outside_Ret14), Time12),
23428      holds_at(playHideAndSeek(Outside_Ret13), Time12)
23429    ]).
23430axiom(holds_at(outside(Outside_Ret13), Time12),
23431   
23432    [ holds_at(outside(Outside_Ret13), Time12),
23433      holds_at(playHideAndSeek(Outside_Ret14), Time12),
23434      holds_at(playHideAndSeek(Outside_Ret13), Time12)
23435    ]).
23436
23437 /*  not(holds_at(outside(Outside_Ret16), Time15)) :-
23438       (   not(holds_at(outside(Outside_Ret16), Time15))
23439       ;   not(holds_at(outside(Outside_Ret17), Time15))
23440       ),
23441       holds_at(playHideAndSeek(Outside_Ret16), Time15),
23442       holds_at(playHideAndSeek(Outside_Ret17), Time15).
23443 */
23444axiom(not(holds_at(outside(Outside_Ret16), Time15)),
23445   
23446    [ not(holds_at(outside(Outside_Ret16), Time15)),
23447      holds_at(playHideAndSeek(Outside_Ret16), Time15),
23448      holds_at(playHideAndSeek(Outside_Ret17), Time15)
23449    ]).
23450axiom(not(holds_at(outside(Outside_Ret16), Time15)),
23451   
23452    [ not(holds_at(outside(Outside_Ret17), Time15)),
23453      holds_at(playHideAndSeek(Outside_Ret16), Time15),
23454      holds_at(playHideAndSeek(Outside_Ret17), Time15)
23455    ]).
23456
23457 /*  not(holds_at(outside(Outside_Ret19), Time18)) :-
23458       (   not(holds_at(outside(Outside_Ret20), Time18))
23459       ;   not(holds_at(outside(Outside_Ret19), Time18))
23460       ),
23461       holds_at(playHideAndSeek(Outside_Ret20), Time18),
23462       holds_at(playHideAndSeek(Outside_Ret19), Time18).
23463 */
23464axiom(not(holds_at(outside(Outside_Ret19), Time18)),
23465   
23466    [ not(holds_at(outside(Outside_Ret20), Time18)),
23467      holds_at(playHideAndSeek(Outside_Ret20), Time18),
23468      holds_at(playHideAndSeek(Outside_Ret19), Time18)
23469    ]).
23470axiom(not(holds_at(outside(Outside_Ret19), Time18)),
23471   
23472    [ not(holds_at(outside(Outside_Ret19), Time18)),
23473      holds_at(playHideAndSeek(Outside_Ret20), Time18),
23474      holds_at(playHideAndSeek(Outside_Ret19), Time18)
23475    ]).
23476
23477
23478% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7326
23479%; End of file.
23480%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23481%; FILE: examples/GiunchigliaEtAl2004/MonkeyPrediction.e
23482%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23483%;
23484%; Copyright (c) 2005 IBM Corporation and others.
23485%; All rights reserved. This program and the accompanying materials
23486%; are made available under the terms of the Common Public License v1.0
23487%; which accompanies this distribution, and is available at
23488%; http://www.eclipse.org/legal/cpl-v10.html
23489%;
23490%; Contributors:
23491%; IBM - Initial implementation
23492%;
23493%; @article{Giunchiglia:2004,
23494%;   author = "Enrico Giunchiglia and Joohyung Lee and Vladimir Lifschitz and Norman C. McCain and Hudson Turner",
23495%;   year = "2004",
23496%;   title = "Nonmonotonic causal theories",
23497%;   journal = "Artificial Intelligence",
23498%;   volume = "153",
23499%;   pages = "49--104",
23500%; }
23501%;
23502%; deduction
23503
23504% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7355
23505% load foundations/Root.e
23506
23507% load foundations/EC.e
23508
23509% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7357
23510% load examples/GiunchigliaEtAl2004/MonkeyBananas.e
23511
23512
23513% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7359
23514% HoldsAt(At(Monkey,L1),0).
23515axiom(initially(at(monkey, l1)),
23516    []).
23517
23518
23519% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7360
23520% HoldsAt(At(Bananas,L2),0).
23521axiom(initially(at(bananas, l2)),
23522    []).
23523
23524
23525% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7361
23526% HoldsAt(At(Box,L3),0).
23527axiom(initially(at(box, l3)),
23528    []).
23529
23530
23531% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7362
23532% Happens(Walk(L3),0).
23533axiom(happens(walk(l3), t),
23534    [is_time(0)]).
23535
23536
23537% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7363
23538% Happens(PushBox(L2),1).
23539axiom(happens(pushBox(l2), start),
23540    [is_time(1), b(t, start), ignore(t+1=start)]).
23541
23542% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7365
23543% completion Happens
23544% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7366
23545==> completion(happens).
23546
23547% range time 0 2
23548% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7368
23549==> range(time,0,2).
23550
23551% range offset 0 0
23552% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7369
23553==> range(offset,0,0).
23554%; End of file.
23555%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23556%; FILE: examples/GiunchigliaEtAl2004/MonkeyPlanning.e
23557%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23558%;
23559%; Copyright (c) 2005 IBM Corporation and others.
23560%; All rights reserved. This program and the accompanying materials
23561%; are made available under the terms of the Common Public License v1.0
23562%; which accompanies this distribution, and is available at
23563%; http://www.eclipse.org/legal/cpl-v10.html
23564%;
23565%; Contributors:
23566%; IBM - Initial implementation
23567%;
23568%; @article{Giunchiglia:2004,
23569%;   author = "Enrico Giunchiglia and Joohyung Lee and Vladimir Lifschitz and Norman C. McCain and Hudson Turner",
23570%;   year = "2004",
23571%;   title = "Nonmonotonic causal theories",
23572%;   journal = "Artificial Intelligence",
23573%;   volume = "153",
23574%;   pages = "49--104",
23575%; }
23576%;
23577%; planning
23578
23579% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7399
23580% load foundations/Root.e
23581
23582% load foundations/EC.e
23583
23584% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7401
23585% load examples/GiunchigliaEtAl2004/MonkeyBananas.e
23586
23587
23588% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7403
23589% HoldsAt(At(Monkey,L1),0).
23590axiom(initially(at(monkey, l1)),
23591    []).
23592
23593
23594% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7404
23595% HoldsAt(At(Bananas,L2),0).
23596axiom(initially(at(bananas, l2)),
23597    []).
23598
23599
23600% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7405
23601% HoldsAt(At(Box,L3),0).
23602axiom(initially(at(box, l3)),
23603    []).
23604
23605
23606% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7406
23607% HoldsAt(HasBananas(),4).
23608holds_at(hasBananas(),4).
23609
23610
23611% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7408
23612%; PLAN Happens(Walk(L3),0).
23613%; PLAN Happens(PushBox(L2),1).
23614%; PLAN Happens(ClimbOn(),2).
23615%; PLAN Happens(GraspBananas(),3).
23616%; one event at a time
23617% [event1,event2,time]
23618 
23619% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7414
23620% Happens(event1,time) & Happens(event2,time) ->
23621% event1=event2.
23622% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7415
23623axiom(Event1=Event2,
23624    [happens(Event1, Time), happens(Event2, Time)]).
23625
23626% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7417
23627% range time 0 4
23628% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7418
23629==> range(time,0,4).
23630
23631% range offset 0 0
23632% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7419
23633==> range(offset,0,0).
23634%; End of file.
23635%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23636%; FILE: examples/GiunchigliaEtAl2004/MonkeyPostdiction.e
23637%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23638%;
23639%; Copyright (c) 2005 IBM Corporation and others.
23640%; All rights reserved. This program and the accompanying materials
23641%; are made available under the terms of the Common Public License v1.0
23642%; which accompanies this distribution, and is available at
23643%; http://www.eclipse.org/legal/cpl-v10.html
23644%;
23645%; Contributors:
23646%; IBM - Initial implementation
23647%;
23648%; @article{Giunchiglia:2004,
23649%;   author = "Enrico Giunchiglia and Joohyung Lee and Vladimir Lifschitz and Norman C. McCain and Hudson Turner",
23650%;   year = "2004",
23651%;   title = "Nonmonotonic causal theories",
23652%;   journal = "Artificial Intelligence",
23653%;   volume = "153",
23654%;   pages = "49--104",
23655%; }
23656%;
23657%; postdiction
23658
23659% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7449
23660% load foundations/Root.e
23661
23662% load foundations/EC.e
23663
23664% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7451
23665% load examples/GiunchigliaEtAl2004/MonkeyBananas.e
23666
23667
23668% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7453
23669% HoldsAt(At(Monkey,L1),0).
23670axiom(initially(at(monkey, l1)),
23671    []).
23672
23673
23674% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7454
23675% HoldsAt(At(Bananas,L2),0).
23676axiom(initially(at(bananas, l2)),
23677    []).
23678
23679
23680% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7455
23681% Happens(Walk(L3),0).
23682axiom(happens(walk(l3), t),
23683    [is_time(0)]).
23684
23685
23686% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7456
23687% Happens(PushBox(L2),1).
23688axiom(happens(pushBox(l2), start),
23689    [is_time(1), b(t, start), ignore(t+1=start)]).
23690
23691% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7458
23692% completion Happens
23693% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7459
23694==> completion(happens).
23695
23696% range time 0 2
23697% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7461
23698==> range(time,0,2).
23699
23700% range offset 0 0
23701% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7462
23702==> range(offset,0,0).
23703%; End of file.
23704%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23705%; FILE: examples/GiunchigliaEtAl2004/MonkeyBananas.e
23706%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
23707%;
23708%; Copyright (c) 2005 IBM Corporation and others.
23709%; All rights reserved. This program and the accompanying materials
23710%; are made available under the terms of the Common Public License v1.0
23711%; which accompanies this distribution, and is available at
23712%; http://www.eclipse.org/legal/cpl-v10.html
23713%;
23714%; Contributors:
23715%; IBM - Initial implementation
23716%;
23717%; @article{Giunchiglia:2004,
23718%;   author = "Enrico Giunchiglia and Joohyung Lee and Vladimir Lifschitz and Norman C. McCain and Hudson Turner",
23719%;   year = "2004",
23720%;   title = "Nonmonotonic causal theories",
23721%;   journal = "Artificial Intelligence",
23722%;   volume = "153",
23723%;   pages = "49--104",
23724%; }
23725%;
23726
23727% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7490
23728% sort object
23729% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7491
23730==> sort(object).
23731
23732% sort location
23733% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7492
23734==> sort(location).
23735
23736% object Monkey, Bananas, Box
23737% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7494
23738==> t(object,monkey).
23739==> t(object,bananas).
23740==> t(object,box).
23741
23742% location L1, L2, L3
23743% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7495
23744==> t(location,l1).
23745==> t(location,l2).
23746==> t(location,l3).
23747
23748% fluent At(object,location)
23749 %  fluent(at(object,location)).
23750% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7497
23751==> mpred_prop(at(object,location),fluent).
23752==> meta_argtypes(at(object,location)).
23753
23754% fluent OnBox()
23755 %  fluent(onBox()).
23756% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7498
23757==> mpred_prop(onBox(),fluent).
23758==> meta_argtypes(onBox()).
23759
23760% fluent HasBananas()
23761 %  fluent(hasBananas()).
23762% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7499
23763==> mpred_prop(hasBananas(),fluent).
23764==> meta_argtypes(hasBananas()).
23765
23766% event Walk(location)
23767 %  event(walk(location)).
23768% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7501
23769==> mpred_prop(walk(location),event).
23770==> meta_argtypes(walk(location)).
23771
23772% event PushBox(location)
23773 %  event(pushBox(location)).
23774% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7502
23775==> mpred_prop(pushBox(location),event).
23776==> meta_argtypes(pushBox(location)).
23777
23778% event ClimbOn()
23779 %  event(climbOn()).
23780% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7503
23781==> mpred_prop(climbOn(),event).
23782==> meta_argtypes(climbOn()).
23783
23784% event ClimbOff()
23785 %  event(climbOff()).
23786% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7504
23787==> mpred_prop(climbOff(),event).
23788==> meta_argtypes(climbOff()).
23789
23790% event GraspBananas()
23791 %  event(graspBananas()).
23792% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7505
23793==> mpred_prop(graspBananas(),event).
23794==> meta_argtypes(graspBananas()).
23795
23796
23797% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7506
23798% [object,location1,location2,time]
23799% HoldsAt(At(object,location1),time) &
23800% HoldsAt(At(object,location2),time) ->
23801% location1=location2.
23802% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7509
23803axiom(Location1=Location2,
23804   
23805    [ holds_at(at(Object, Location1), Time),
23806      holds_at(at(Object, Location2), Time)
23807    ]).
23808
23809
23810% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7511
23811% [object,location,time]
23812% object=% Monkey ->
23813% Initiates(Walk(location),At(object,location),time).
23814% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7513
23815axiom(initiates(walk(Location), at(Object, Location), Time),
23816    [equals(Object, monkey)]).
23817
23818
23819% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7515
23820% [object,location1,location2,time]
23821% object=% Monkey &
23822% HoldsAt(At(object,location1),time) ->
23823% Terminates(Walk(location2),At(object,location1),time).
23824% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7518
23825axiom(terminates(walk(Location2), at(Object, Location1), Time),
23826   
23827    [ equals(Object, monkey),
23828      holds_at(at(Object, Location1), Time)
23829    ]).
23830
23831
23832% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7520
23833% [location,time]
23834% Happens(Walk(location),time) ->
23835% !HoldsAt(At(Monkey,location),time) &
23836% !HoldsAt(OnBox(),time).
23837% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7523
23838axiom(requires(walk(Location), Time),
23839   
23840    [ not(holds_at(at(monkey, Location), Time)),
23841      not(holds_at(onBox(), Time))
23842    ]).
23843
23844
23845% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7525
23846% [location,time]
23847% HoldsAt(HasBananas(),time) &
23848% HoldsAt(At(Monkey,location),time) ->
23849% HoldsAt(At(Bananas,location),time).
23850% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7528
23851axiom(holds_at(at(bananas, Location), Time),
23852   
23853    [ holds_at(hasBananas(), Time),
23854      holds_at(at(monkey, Location), Time)
23855    ]).
23856
23857
23858% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7530
23859% [object,location,time]
23860% object=% Box | object=Monkey ->
23861% Initiates(PushBox(location),At(object,location),time).
23862% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7532
23863axiom(initiates(pushBox(Location), at(Object, Location), Time),
23864    [equals(Object, box)]).
23865axiom(initiates(pushBox(Location), at(Object, Location), Time),
23866    [equals(Object, monkey)]).
23867
23868
23869% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7534
23870% [object,location1,location2,time]
23871% (object=Box | object=Monkey) &
23872% HoldsAt(At(object,location1),time) ->
23873% Terminates(PushBox(location2),At(object,location1),time).
23874% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7537
23875axiom(terminates(pushBox(Location2), at(Object, Location1), Time),
23876   
23877    [ equals(Object, box),
23878      holds_at(at(Object, Location1), Time)
23879    ]).
23880axiom(terminates(pushBox(Location2), at(Object, Location1), Time),
23881   
23882    [ equals(Object, monkey),
23883      holds_at(at(Object, Location1), Time)
23884    ]).
23885
23886
23887% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7539
23888% [location,time]
23889% Happens(PushBox(location),time) ->
23890% ({location1}
23891%   HoldsAt(At(Box,location1),time) &
23892%   HoldsAt(At(Monkey,location1),time)) &
23893% !HoldsAt(At(Monkey,location),time) &
23894% !HoldsAt(OnBox(),time).
23895% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7545
23896axiom(requires(pushBox(Location), Time),
23897   
23898    [ holds_at(at(box, Location1), Time),
23899      holds_at(at(monkey, Location1), Time),
23900      not(holds_at(at(monkey, Location), Time)),
23901      not(holds_at(onBox(), Time))
23902    ]).
23903
23904
23905% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7547
23906% [time]
23907 % Initiates(ClimbOn(),OnBox(),time).
23908axiom(initiates(climbOn(), onBox(), Time),
23909    []).
23910
23911
23912% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7549
23913% [time]
23914% Happens(ClimbOn(),time) ->
23915% !HoldsAt(OnBox(),time).
23916% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7551
23917axiom(requires(climbOn(), Time),
23918    [not(holds_at(onBox(), Time))]).
23919
23920
23921% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7553
23922% [time]
23923 % Terminates(ClimbOff(),OnBox(),time).
23924axiom(terminates(climbOff(), onBox(), Time),
23925    []).
23926
23927
23928% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7555
23929% [time]
23930% Happens(ClimbOff(),time) ->
23931% HoldsAt(OnBox(),time).
23932% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7557
23933axiom(requires(climbOff(), Time),
23934    [holds_at(onBox(), Time)]).
23935
23936
23937% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7559
23938% [time]
23939 % Initiates(GraspBananas(),HasBananas(),time).
23940axiom(initiates(graspBananas(), hasBananas(), Time),
23941    []).
23942
23943
23944% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7561
23945% [object,location,time]
23946% object=% Bananas ->
23947% Releases(GraspBananas(),At(object,location),time).
23948% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7563
23949axiom(releases(graspBananas(), at(Object, Location), Time),
23950    [equals(Object, bananas)]).
23951
23952
23953% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7565
23954% [time]
23955% Happens(GraspBananas(),time) ->
23956% ({location1}
23957%   HoldsAt(At(Bananas,location1),time) &
23958%   HoldsAt(At(Monkey,location1),time)) &
23959% HoldsAt(OnBox(),time).
23960% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7570
23961axiom(requires(graspBananas(), Time),
23962   
23963    [ holds_at(at(bananas, Location1), Time),
23964      holds_at(at(monkey, Location1), Time),
23965      holds_at(onBox(), Time)
23966    ]).
23967
23968
23969% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7572
23970% [time]
23971% HoldsAt(OnBox(),time) ->
23972% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7574
23973% {location1}%  HoldsAt(At(Box,location1),time) &
23974%             HoldsAt(At(Monkey,location1),time).
23975
23976 /*   exists([Location1],
23977             if(holds_at(onBox(), Time),
23978                 (holds_at(at(box, Location1), Time), holds_at(at(monkey, Location1), Time)))).
23979 */
23980
23981 /*  not(some(Location, '$kolem_Fn_370'(Time3))) :-
23982       holds_at(onBox(), Time3),
23983       (   not(holds_at(at(box, Location), Time3))
23984       ;   not(holds_at(at(monkey, Location), Time3))
23985       ).
23986 */
23987% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7575
23988axiom(not(some(Location, '$kolem_Fn_370'(Time3))),
23989   
23990    [ not(holds_at(at(box, Location), Time3)),
23991      holds_at(onBox(), Time3)
23992    ]).
23993axiom(not(some(Location, '$kolem_Fn_370'(Time3))),
23994   
23995    [ not(holds_at(at(monkey, Location), Time3)),
23996      holds_at(onBox(), Time3)
23997    ]).
23998
23999 /*  not(holds_at(onBox(), Time5)) :-
24000       (   not(holds_at(at(box, Location6), Time5))
24001       ;   not(holds_at(at(monkey, Location6), Time5))
24002       ),
24003       some(Location6, '$kolem_Fn_370'(Time5)).
24004 */
24005axiom(not(holds_at(onBox(), Time5)),
24006   
24007    [ not(holds_at(at(box, Location6), Time5)),
24008      some(Location6, '$kolem_Fn_370'(Time5))
24009    ]).
24010axiom(not(holds_at(onBox(), Time5)),
24011   
24012    [ not(holds_at(at(monkey, Location6), Time5)),
24013      some(Location6, '$kolem_Fn_370'(Time5))
24014    ]).
24015
24016 /*  holds_at(at(box, Location7), Time8) :-
24017       holds_at(onBox(), Time8),
24018       some(Location7, '$kolem_Fn_370'(Time8)).
24019 */
24020axiom(holds_at(at(box, Location7), Time8),
24021   
24022    [ holds_at(onBox(), Time8),
24023      some(Location7, '$kolem_Fn_370'(Time8))
24024    ]).
24025
24026 /*  holds_at(at(monkey, Location9), Time10) :-
24027       holds_at(onBox(), Time10),
24028       some(Location9, '$kolem_Fn_370'(Time10)).
24029 */
24030axiom(holds_at(at(monkey, Location9), Time10),
24031   
24032    [ holds_at(onBox(), Time10),
24033      some(Location9, '$kolem_Fn_370'(Time10))
24034    ]).
24035
24036
24037% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7577
24038%; End of file.
24039%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24040%; FILE: examples/Antoniou1997/Student.e
24041%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24042%;
24043%; Copyright (c) 2005 IBM Corporation and others.
24044%; All rights reserved. This program and the accompanying materials
24045%; are made available under the terms of the Common Public License v1.0
24046%; which accompanies this distribution, and is available at
24047%; http://www.eclipse.org/legal/cpl-v10.html
24048%;
24049%; Contributors:
24050%; IBM - Initial implementation
24051%;
24052%; conflicting defaults: method (D)
24053%; \fullciteA[p. 157]{Antoniou:1997}
24054%;
24055%; @book{Antoniou:1997,
24056%;   author = "Grigoris Antoniou",
24057%;   year = "1997",
24058%;   title = "Nonmonotonic Reasoning",
24059%;   address = "Cambridge, MA",
24060%;   publisher = "MIT Press",
24061%; }
24062%;
24063
24064% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7606
24065% load foundations/Root.e
24066
24067% load foundations/EC.e
24068
24069% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7609
24070% sort x
24071% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7610
24072==> sort(x).
24073
24074% predicate Adult(x)
24075 %  predicate(adult(x)).
24076% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7612
24077==> mpred_prop(adult(x),predicate).
24078==> meta_argtypes(adult(x)).
24079
24080% predicate Student(x)
24081 %  predicate(student(x)).
24082% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7613
24083==> mpred_prop(student(x),predicate).
24084==> meta_argtypes(student(x)).
24085
24086% predicate Employed(x)
24087 %  predicate(employed(x)).
24088% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7614
24089==> mpred_prop(employed(x),predicate).
24090==> meta_argtypes(employed(x)).
24091
24092% predicate Ab1(x)
24093 %  predicate(ab1(x)).
24094% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7615
24095==> mpred_prop(ab1(x),predicate).
24096==> meta_argtypes(ab1(x)).
24097
24098% predicate Ab2(x)
24099 %  predicate(ab2(x)).
24100% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7616
24101==> mpred_prop(ab2(x),predicate).
24102==> meta_argtypes(ab2(x)).
24103
24104% x Mary
24105% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7618
24106==> t(x,mary).
24107
24108
24109% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7619
24110% Student(Mary).
24111student(mary).
24112
24113
24114% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7621
24115% [x]
24116 % Adult(x) & !Ab1(x) -> Employed(x).
24117axiom(employed(X),
24118    [adult(X), not(ab1(X))]).
24119
24120
24121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7622
24122% [x]
24123 % Student(x) & !Ab2(x) -> !Employed(x).
24124axiom(not(employed(X)),
24125    [student(X), not(ab2(X))]).
24126
24127
24128% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7623
24129% [x]
24130 % Student(x) -> Adult(x).
24131axiom(adult(X),
24132    [student(X)]).
24133
24134% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7624
24135% Theta: 
24136next_axiom_uses(theta).
24137 
24138
24139
24140% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7624
24141% [x]
24142 % Student(x) -> Ab1(x).
24143axiom(ab1(X),
24144    [student(X)]).
24145
24146% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7626
24147% range time 0 0
24148% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7627
24149==> range(time,0,0).
24150
24151% range offset 1 1
24152% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7628
24153==> range(offset,1,1).
24154
24155% completion Theta Ab1
24156% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7630
24157==> completion(theta).
24158==> completion(ab1).
24159
24160% completion Theta Ab2
24161% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7631
24162==> completion(theta).
24163==> completion(ab2).
24164%; End of file.
24165%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24166%; FILE: examples/Antoniou1997/Dropout.e
24167%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24168%;
24169%; Copyright (c) 2005 IBM Corporation and others.
24170%; All rights reserved. This program and the accompanying materials
24171%; are made available under the terms of the Common Public License v1.0
24172%; which accompanies this distribution, and is available at
24173%; http://www.eclipse.org/legal/cpl-v10.html
24174%;
24175%; Contributors:
24176%; IBM - Initial implementation
24177%;
24178%; dealing with conflicting defaults by adding conditions
24179%; to one of the conflicting rules
24180%; \fullciteA[p. 56]{Antoniou:1997}
24181%;
24182%; @book{Antoniou:1997,
24183%;   author = "Grigoris Antoniou",
24184%;   year = "1997",
24185%;   title = "Nonmonotonic Reasoning",
24186%;   address = "Cambridge, MA",
24187%;   publisher = "MIT Press",
24188%; }
24189%;
24190
24191% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7662
24192% load foundations/Root.e
24193
24194% load foundations/EC.e
24195
24196% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7665
24197% sort x
24198% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7666
24199==> sort(x).
24200
24201% predicate Dropout(x)
24202 %  predicate(dropout(x)).
24203% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7668
24204==> mpred_prop(dropout(x),predicate).
24205==> meta_argtypes(dropout(x)).
24206
24207% predicate Adult(x)
24208 %  predicate(adult(x)).
24209% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7669
24210==> mpred_prop(adult(x),predicate).
24211==> meta_argtypes(adult(x)).
24212
24213% predicate Employed(x)
24214 %  predicate(employed(x)).
24215% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7670
24216==> mpred_prop(employed(x),predicate).
24217==> meta_argtypes(employed(x)).
24218
24219% predicate Ab1(x)
24220 %  predicate(ab1(x)).
24221% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7671
24222==> mpred_prop(ab1(x),predicate).
24223==> meta_argtypes(ab1(x)).
24224
24225% predicate Ab2(x)
24226 %  predicate(ab2(x)).
24227% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7672
24228==> mpred_prop(ab2(x),predicate).
24229==> meta_argtypes(ab2(x)).
24230
24231% x Bill
24232% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7674
24233==> t(x,bill).
24234
24235
24236% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7675
24237% Dropout(Bill).
24238dropout(bill).
24239
24240
24241% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7677
24242% [x]
24243 % Dropout(x) & !Ab1(x) -> Adult(x).
24244axiom(adult(X),
24245    [dropout(X), not(ab1(X))]).
24246
24247
24248% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7678
24249% [x]
24250 % Adult(x) & !Dropout(x) & !Ab2(x) -> Employed(x).
24251axiom(employed(X),
24252    [adult(X), not(dropout(X)), not(ab2(X))]).
24253
24254% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7680
24255% range time 0 0
24256% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7681
24257==> range(time,0,0).
24258
24259% range offset 1 1
24260% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7682
24261==> range(offset,1,1).
24262
24263% completion Theta Ab1
24264% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7684
24265==> completion(theta).
24266==> completion(ab1).
24267
24268% completion Theta Ab2
24269% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7685
24270==> completion(theta).
24271==> completion(ab2).
24272%; End of file.
24273%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24274%; FILE: examples/Shanahan1999/Happy.e
24275%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24276%;
24277%; Copyright (c) 2005 IBM Corporation and others.
24278%; All rights reserved. This program and the accompanying materials
24279%; are made available under the terms of the Common Public License v1.0
24280%; which accompanies this distribution, and is available at
24281%; http://www.eclipse.org/legal/cpl-v10.html
24282%;
24283%; Contributors:
24284%; IBM - Initial implementation
24285%;
24286%; @incollection{Shanahan:1999,
24287%;   author = "Shanahan, Murray",
24288%;   year = "1999",
24289%;   title = "The Event Calculus explained",
24290%;   editor = "Michael J. Wooldridge and Manuela M. Veloso",
24291%;   booktitle = "Artificial Intelligence Today: Recent Trends and Developments",
24292%;   series = "Lecture Notes in Computer Science",
24293%;   volume = "1600",
24294%;   pages = "409--430",
24295%;   address = "Berlin",
24296%;   publisher = "Springer",
24297%; }
24298%;
24299%; deduction
24300%;
24301%; modifications from Shanahan's formulation:
24302%; InitiallyN -> !HoldsAt
24303%; InitiallyP -> HoldsAt
24304%; timestamps
24305%;
24306
24307% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7724
24308% load foundations/Root.e
24309
24310% load foundations/EC.e
24311
24312% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7727
24313% sort person
24314% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7728
24315==> sort(person).
24316
24317% event Feed(person)
24318 %  event(feed(person)).
24319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7729
24320==> mpred_prop(feed(person),event).
24321==> meta_argtypes(feed(person)).
24322
24323% event Clothe(person)
24324 %  event(clothe(person)).
24325% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7730
24326==> mpred_prop(clothe(person),event).
24327==> meta_argtypes(clothe(person)).
24328
24329% fluent Happy(person)
24330 %  fluent(happy(person)).
24331% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7731
24332==> mpred_prop(happy(person),fluent).
24333==> meta_argtypes(happy(person)).
24334
24335% fluent Hungry(person)
24336 %  fluent(hungry(person)).
24337% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7732
24338==> mpred_prop(hungry(person),fluent).
24339==> meta_argtypes(hungry(person)).
24340
24341% fluent Cold(person)
24342 %  fluent(cold(person)).
24343% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7733
24344==> mpred_prop(cold(person),fluent).
24345==> meta_argtypes(cold(person)).
24346
24347% noninertial Happy
24348% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7734
24349==> noninertial(happy).
24350
24351
24352% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7735
24353% [person,time]
24354% HoldsAt(Happy(person),time) <->
24355% !HoldsAt(Hungry(person),time) &
24356% !HoldsAt(Cold(person),time).
24357
24358 /*  holds_at(happy(Person), Time) <->
24359       not(holds_at(hungry(Person), Time)),
24360       not(holds_at(cold(Person), Time)).
24361 */
24362% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7738
24363axiom(holds_at(happy(Person), Time),
24364   
24365    [ not(holds_at(hungry(Person), Time)),
24366      not(holds_at(cold(Person), Time))
24367    ]).
24368
24369 /*   if(holds_at(happy(Person), Time),
24370          (not(holds_at(hungry(Person), Time)), not(holds_at(cold(Person), Time)))).
24371 */
24372
24373 /*  not(holds_at(happy(Happy_Ret), Time2)) :-
24374       (   holds_at(hungry(Happy_Ret), Time2)
24375       ;   holds_at(cold(Happy_Ret), Time2)
24376       ).
24377 */
24378axiom(not(holds_at(happy(Happy_Ret), Time2)),
24379    [holds_at(hungry(Happy_Ret), Time2)]).
24380axiom(not(holds_at(happy(Happy_Ret), Time2)),
24381    [holds_at(cold(Happy_Ret), Time2)]).
24382
24383 /*  not(holds_at(hungry(Hungry_Ret), Time4)) :-
24384       holds_at(happy(Hungry_Ret), Time4).
24385 */
24386axiom(not(holds_at(hungry(Hungry_Ret), Time4)),
24387    [holds_at(happy(Hungry_Ret), Time4)]).
24388
24389 /*  not(holds_at(cold(Cold_Ret), Time6)) :-
24390       holds_at(happy(Cold_Ret), Time6).
24391 */
24392axiom(not(holds_at(cold(Cold_Ret), Time6)),
24393    [holds_at(happy(Cold_Ret), Time6)]).
24394
24395
24396% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7740
24397% [person,time]
24398% Terminates(Feed(person),Hungry(person),time).
24399% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7741
24400axiom(terminates(feed(Person), hungry(Person), Time),
24401    []).
24402
24403
24404% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7743
24405% [person,time]
24406% Terminates(Clothe(person),Cold(person),time).
24407% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7744
24408axiom(terminates(clothe(Person), cold(Person), Time),
24409    []).
24410
24411% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7746
24412% person Fred
24413% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7747
24414==> t(person,fred).
24415
24416
24417% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7748
24418% HoldsAt(Hungry(Fred),0).
24419axiom(initially(hungry(fred)),
24420    []).
24421
24422
24423% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7749
24424% !HoldsAt(Cold(Fred),0).
24425 %  not(initially(cold(fred))).
24426axiom(not(initially(cold(fred))),
24427    []).
24428
24429
24430% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7750
24431% Happens(Feed(Fred),1).
24432axiom(happens(feed(fred), start),
24433    [is_time(1), b(t, start), ignore(t+1=start)]).
24434
24435% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7752
24436% completion Happens
24437% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7753
24438==> completion(happens).
24439
24440% range time 0 2
24441% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7755
24442==> range(time,0,2).
24443
24444% range offset 1 1
24445% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7756
24446==> range(offset,1,1).
24447%; End of file.
24448%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24449%; FILE: examples/Shanahan1999/ThielscherCircuit.e
24450%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24451%;
24452%; Copyright (c) 2005 IBM Corporation and others.
24453%; All rights reserved. This program and the accompanying materials
24454%; are made available under the terms of the Common Public License v1.0
24455%; which accompanies this distribution, and is available at
24456%; http://www.eclipse.org/legal/cpl-v10.html
24457%;
24458%; Contributors:
24459%; IBM - Initial implementation
24460%;
24461%; @article{Thielscher:1997,
24462%;   author = "Michael Thielscher",
24463%;   year = "1997",
24464%;   title = "Ramification and causality",
24465%;   journal = "Artificial Intelligence",
24466%;   volume = "89",
24467%;   pages = "317--364",
24468%; }
24469%;
24470%; @incollection{Shanahan:1999,
24471%;   author = "Shanahan, Murray",
24472%;   year = "1999",
24473%;   title = "The Event Calculus explained",
24474%;   editor = "Michael J. Wooldridge and Manuela M. Veloso",
24475%;   booktitle = "Artificial Intelligence Today: Recent Trends and Developments",
24476%;   series = "Lecture Notes in Computer Science",
24477%;   volume = "1600",
24478%;   pages = "409--430",
24479%;   address = "Berlin",
24480%;   publisher = "Springer",
24481%; }
24482%;
24483%; deduction
24484%;
24485%; modifications from Shanahan's formulation:
24486%; timestamps
24487%;
24488
24489% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7802
24490% load foundations/Root.e
24491
24492% load foundations/EC.e
24493
24494% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7804
24495% load foundations/ECCausal.e
24496
24497% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7806
24498% event LightOn()
24499 %  event(lightOn()).
24500% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7807
24501==> mpred_prop(lightOn(),event).
24502==> meta_argtypes(lightOn()).
24503
24504% event Close1()
24505 %  event(close1()).
24506% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7808
24507==> mpred_prop(close1(),event).
24508==> meta_argtypes(close1()).
24509
24510% event Open2()
24511 %  event(open2()).
24512% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7809
24513==> mpred_prop(open2(),event).
24514==> meta_argtypes(open2()).
24515
24516% event CloseRelay()
24517 %  event(closeRelay()).
24518% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7810
24519==> mpred_prop(closeRelay(),event).
24520==> meta_argtypes(closeRelay()).
24521
24522% fluent Light()
24523 %  fluent(light()).
24524% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7812
24525==> mpred_prop(light(),fluent).
24526==> meta_argtypes(light()).
24527
24528% fluent Switch1()
24529 %  fluent(switch1()).
24530% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7813
24531==> mpred_prop(switch1(),fluent).
24532==> meta_argtypes(switch1()).
24533
24534% fluent Switch2()
24535 %  fluent(switch2()).
24536% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7814
24537==> mpred_prop(switch2(),fluent).
24538==> meta_argtypes(switch2()).
24539
24540% fluent Switch3()
24541 %  fluent(switch3()).
24542% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7815
24543==> mpred_prop(switch3(),fluent).
24544==> meta_argtypes(switch3()).
24545
24546% fluent Relay()
24547 %  fluent(relay()).
24548% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7816
24549==> mpred_prop(relay(),fluent).
24550==> meta_argtypes(relay()).
24551
24552
24553% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7817
24554% [time]
24555% Stopped(Light(),time) &
24556% Initiated(Switch1(),time) &
24557% Initiated(Switch2(),time) ->
24558% Happens(LightOn(),time).
24559% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7821
24560axiom(happens(lightOn(), Time),
24561   
24562    [ stopped(light(), Time),
24563      initiated(switch1(), Time),
24564      initiated(switch2(), Time)
24565    ]).
24566
24567
24568% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7823
24569% [time]
24570% Started(Switch2(),time) &
24571% Initiated(Relay(),time) ->
24572% Happens(Open2(),time).
24573% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7826
24574axiom(happens(open2(), Time),
24575    [started(switch2(), Time), initiated(relay(), Time)]).
24576
24577
24578% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7828
24579% [time]
24580% Stopped(Relay(),time) &
24581% Initiated(Switch1(),time) &
24582% Initiated(Switch3(),time) ->
24583% Happens(CloseRelay(),time).
24584% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7832
24585axiom(happens(closeRelay(), Time),
24586   
24587    [ stopped(relay(), Time),
24588      initiated(switch1(), Time),
24589      initiated(switch3(), Time)
24590    ]).
24591
24592
24593% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7834
24594% [time]
24595 % Initiates(LightOn(),Light(),time).
24596axiom(initiates(lightOn(), light(), Time),
24597    []).
24598
24599
24600% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7836
24601% [time]
24602 % Terminates(Open2(),Switch2(),time).
24603axiom(terminates(open2(), switch2(), Time),
24604    []).
24605
24606
24607% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7838
24608% [time]
24609 % Initiates(CloseRelay(),Relay(),time).
24610axiom(initiates(closeRelay(), relay(), Time),
24611    []).
24612
24613
24614% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7840
24615% [time]
24616 % Initiates(Close1(),Switch1(),time).
24617axiom(initiates(close1(), switch1(), Time),
24618    []).
24619
24620
24621% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7842
24622% !HoldsAt(Switch1(),0).
24623 %  not(initially(switch1())).
24624axiom(not(initially(switch1())),
24625    []).
24626
24627
24628% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7843
24629% HoldsAt(Switch2(),0).
24630axiom(initially(switch2()),
24631    []).
24632
24633
24634% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7844
24635% HoldsAt(Switch3(),0).
24636axiom(initially(switch3()),
24637    []).
24638
24639
24640% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7845
24641% !HoldsAt(Relay(),0).
24642 %  not(initially(relay())).
24643axiom(not(initially(relay())),
24644    []).
24645
24646
24647% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7846
24648% !HoldsAt(Light(),0).
24649 %  not(initially(light())).
24650axiom(not(initially(light())),
24651    []).
24652
24653
24654% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7848
24655% Happens(Close1(),0).
24656axiom(happens(close1(), t),
24657    [is_time(0)]).
24658
24659% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7850
24660% completion Happens
24661% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7851
24662==> completion(happens).
24663
24664% range time 0 1
24665% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7853
24666==> range(time,0,1).
24667
24668% range offset 1 1
24669% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7854
24670==> range(offset,1,1).
24671%; End of file.
24672%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24673%; FILE: examples/Shanahan1999/CoinToss.e
24674%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24675%;
24676%; Copyright (c) 2005 IBM Corporation and others.
24677%; All rights reserved. This program and the accompanying materials
24678%; are made available under the terms of the Common Public License v1.0
24679%; which accompanies this distribution, and is available at
24680%; http://www.eclipse.org/legal/cpl-v10.html
24681%;
24682%; Contributors:
24683%; IBM - Initial implementation
24684%;
24685%; @article{Kartha:1994,
24686%;   author = "G. Neelakantan Kartha",
24687%;   year = "1994",
24688%;   title = "Two counterexamples related to \uppercase{B}aker's approach to the frame problem",
24689%;   journal = "Artificial Intelligence",
24690%;   volume = "69",
24691%;   number = "1--2",
24692%;   pages = "379--391",
24693%; }
24694%;
24695%; @incollection{Shanahan:1999,
24696%;   author = "Shanahan, Murray",
24697%;   year = "1999",
24698%;   title = "The Event Calculus explained",
24699%;   editor = "Michael J. Wooldridge and Manuela M. Veloso",
24700%;   booktitle = "Artificial Intelligence Today: Recent Trends and Developments",
24701%;   series = "Lecture Notes in Computer Science",
24702%;   volume = "1600",
24703%;   pages = "409--430",
24704%;   address = "Berlin",
24705%;   publisher = "Springer",
24706%; }
24707%;
24708%; model finding
24709%;
24710%; modifications from Shanahan's formulation:
24711%; InitiallyP -> HoldsAt
24712%; pruning of models irrelevant to example
24713%; timestamps
24714%;
24715
24716% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7903
24717% load foundations/Root.e
24718
24719% load foundations/EC.e
24720
24721% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7906
24722% event Toss()
24723 %  event(toss()).
24724% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7907
24725==> mpred_prop(toss(),event).
24726==> meta_argtypes(toss()).
24727
24728% fluent ItsHeads()
24729 %  fluent(itsHeads()).
24730% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7908
24731==> mpred_prop(itsHeads(),fluent).
24732==> meta_argtypes(itsHeads()).
24733
24734% fluent Heads()
24735 %  fluent(heads()).
24736% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7909
24737==> mpred_prop(heads(),fluent).
24738==> meta_argtypes(heads()).
24739
24740% noninertial ItsHeads
24741% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7910
24742==> noninertial(itsHeads).
24743
24744
24745% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7911
24746% [time]
24747 % HoldsAt(ItsHeads(),time) -> Initiates(Toss(),Heads(),time).
24748axiom(initiates(toss(), heads(), Time),
24749    [holds_at(itsHeads(), Time)]).
24750
24751
24752% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7912
24753% [time]
24754 % !HoldsAt(ItsHeads(),time) -> Terminates(Toss(),Heads(),time).
24755axiom(terminates(toss(), heads(), Time),
24756    [not(holds_at(itsHeads(), Time))]).
24757
24758
24759% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7914
24760% HoldsAt(Heads(),0).
24761axiom(initially(heads()),
24762    []).
24763
24764
24765% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7915
24766% Happens(Toss(),1).
24767axiom(happens(toss(), start),
24768    [is_time(1), b(t, start), ignore(t+1=start)]).
24769
24770
24771% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7916
24772% Happens(Toss(),2).
24773axiom(happens(toss(), t2),
24774    [is_time(2), b(t, t2), ignore(t+2=t2)]).
24775
24776
24777% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7917
24778% Happens(Toss(),3).
24779axiom(happens(toss(), t3),
24780    [is_time(3), b(t, t3), ignore(t+3=t3)]).
24781
24782
24783% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7919
24784%; prune models irrelevant to example:
24785
24786
24787% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7920
24788% HoldsAt(ItsHeads(),0).
24789axiom(initially(itsHeads()),
24790    []).
24791
24792
24793% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7921
24794% HoldsAt(ItsHeads(),4).
24795holds_at(itsHeads(),4).
24796
24797% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7923
24798% completion Happens
24799% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7924
24800==> completion(happens).
24801
24802% range time 0 4
24803% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7926
24804==> range(time,0,4).
24805
24806% range offset 1 1
24807% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7927
24808==> range(offset,1,1).
24809%; End of file.
24810%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24811%; FILE: examples/Shanahan1999/ChessBoard.e
24812%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24813%;
24814%; Copyright (c) 2005 IBM Corporation and others.
24815%; All rights reserved. This program and the accompanying materials
24816%; are made available under the terms of the Common Public License v1.0
24817%; which accompanies this distribution, and is available at
24818%; http://www.eclipse.org/legal/cpl-v10.html
24819%;
24820%; Contributors:
24821%; IBM - Initial implementation
24822%;
24823%; due to Raymond Reiter
24824%;
24825%; @inproceedings{KarthaLifschitz:1994,
24826%;   author = "G. Neelakantan Kartha and Vladimir Lifschitz",
24827%;   year = "1994",
24828%;   title = "Actions with indirect effects (preliminary report)",
24829%;   editor = "Jon Doyle and Erik Sandewall and Pietro Torasso",
24830%;   booktitle = "\uppercase{P}roceedings of the \uppercase{F}ourth \uppercase{I}nternational \uppercase{C}onference on \uppercase{P}rinciples of \uppercase{K}nowledge \uppercase{R}epresentation and \uppercase{R}easoning",
24831%;   pages = "341--350",
24832%;   address = "San Francisco",
24833%;   publisher = "Morgan Kaufmann",
24834%; }
24835%;
24836%; @incollection{Shanahan:1999,
24837%;   author = "Shanahan, Murray",
24838%;   year = "1999",
24839%;   title = "The Event Calculus explained",
24840%;   editor = "Michael J. Wooldridge and Manuela M. Veloso",
24841%;   booktitle = "Artificial Intelligence Today: Recent Trends and Developments",
24842%;   series = "Lecture Notes in Computer Science",
24843%;   volume = "1600",
24844%;   pages = "409--430",
24845%;   address = "Berlin",
24846%;   publisher = "Springer",
24847%; }
24848%;
24849%; model finding
24850%;
24851%; modifications from Shanahan's formulation:
24852%; InitiallyN -> !HoldsAt
24853%; pruning of models irrelevant to example
24854%; timestamps
24855%;
24856
24857% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7979
24858% load foundations/Root.e
24859
24860% load foundations/EC.e
24861
24862% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7982
24863% event Throw()
24864 %  event(throw()).
24865% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7983
24866==> mpred_prop(throw(),event).
24867==> meta_argtypes(throw()).
24868
24869% fluent ItsBlack()
24870 %  fluent(itsBlack()).
24871% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7984
24872==> mpred_prop(itsBlack(),fluent).
24873==> meta_argtypes(itsBlack()).
24874
24875% fluent ItsWhite()
24876 %  fluent(itsWhite()).
24877% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7985
24878==> mpred_prop(itsWhite(),fluent).
24879==> meta_argtypes(itsWhite()).
24880
24881% fluent OnBlack()
24882 %  fluent(onBlack()).
24883% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7986
24884==> mpred_prop(onBlack(),fluent).
24885==> meta_argtypes(onBlack()).
24886
24887% fluent OnWhite()
24888 %  fluent(onWhite()).
24889% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7987
24890==> mpred_prop(onWhite(),fluent).
24891==> meta_argtypes(onWhite()).
24892
24893% noninertial ItsBlack, ItsWhite
24894% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7988
24895==> noninertial(itsBlack).
24896==> noninertial(itsWhite).
24897
24898
24899% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7989
24900% [time]
24901% HoldsAt(ItsWhite(),time) ->
24902% Initiates(Throw(),OnWhite(),time).
24903% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7991
24904axiom(initiates(throw(), onWhite(), Time),
24905    [holds_at(itsWhite(), Time)]).
24906
24907
24908% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7993
24909% [time]
24910% HoldsAt(ItsBlack(),time) ->
24911% Initiates(Throw(),OnBlack(),time).
24912% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7995
24913axiom(initiates(throw(), onBlack(), Time),
24914    [holds_at(itsBlack(), Time)]).
24915
24916
24917% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7997
24918% [time]
24919 % HoldsAt(ItsWhite(),time) | HoldsAt(ItsBlack(),time).
24920
24921 /*   (   holds_at(itsWhite(), Time)
24922      ;   holds_at(itsBlack(), Time)
24923      ).
24924 */
24925
24926 /*  holds_at(itsWhite(), Time1) :-
24927       not(holds_at(itsBlack(), Time1)).
24928 */
24929axiom(holds_at(itsWhite(), Time1),
24930    [not(holds_at(itsBlack(), Time1))]).
24931
24932 /*  holds_at(itsBlack(), Time2) :-
24933       not(holds_at(itsWhite(), Time2)).
24934 */
24935axiom(holds_at(itsBlack(), Time2),
24936    [not(holds_at(itsWhite(), Time2))]).
24937
24938
24939% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:7999
24940% !HoldsAt(OnWhite(),0).
24941 %  not(initially(onWhite())).
24942axiom(not(initially(onWhite())),
24943    []).
24944
24945
24946% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8000
24947% !HoldsAt(OnBlack(),0).
24948 %  not(initially(onBlack())).
24949axiom(not(initially(onBlack())),
24950    []).
24951
24952
24953% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8001
24954% Happens(Throw(),1).
24955axiom(happens(throw(), start),
24956    [is_time(1), b(t, start), ignore(t+1=start)]).
24957
24958
24959% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8003
24960%; prune models irrelevant to example:
24961
24962
24963% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8004
24964% HoldsAt(ItsWhite(),0).
24965axiom(initially(itsWhite()),
24966    []).
24967
24968
24969% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8005
24970% HoldsAt(ItsBlack(),0).
24971axiom(initially(itsBlack()),
24972    []).
24973
24974
24975% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8006
24976% HoldsAt(ItsWhite(),2).
24977holds_at(itsWhite(),2).
24978
24979
24980% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8007
24981% HoldsAt(ItsBlack(),2).
24982holds_at(itsBlack(),2).
24983
24984% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8009
24985% completion Happens
24986% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8010
24987==> completion(happens).
24988
24989% range time 0 2
24990% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8012
24991==> range(time,0,2).
24992
24993% range offset 1 1
24994% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8013
24995==> range(offset,1,1).
24996%; End of file.
24997%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
24998%; FILE: examples/Shanahan1999/RussianTurkey.e
24999%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25000%;
25001%; Copyright (c) 2005 IBM Corporation and others.
25002%; All rights reserved. This program and the accompanying materials
25003%; are made available under the terms of the Common Public License v1.0
25004%; which accompanies this distribution, and is available at
25005%; http://www.eclipse.org/legal/cpl-v10.html
25006%;
25007%; Contributors:
25008%; IBM - Initial implementation
25009%;
25010%; @book{Sandewall:1994,
25011%;   author = "Sandewall, Erik",
25012%;   year = "1994",
25013%;   title = "Features and Fluents: The Representation of Knowledge about Dynamical Systems",
25014%;   volume = "I",
25015%;   address = "Oxford",
25016%;   publisher = "Oxford University Press",
25017%; }
25018%;
25019%; @incollection{Shanahan:1999,
25020%;   author = "Shanahan, Murray",
25021%;   year = "1999",
25022%;   title = "The Event Calculus explained",
25023%;   editor = "Michael J. Wooldridge and Manuela M. Veloso",
25024%;   booktitle = "Artificial Intelligence Today: Recent Trends and Developments",
25025%;   series = "Lecture Notes in Computer Science",
25026%;   volume = "1600",
25027%;   pages = "409--430",
25028%;   address = "Berlin",
25029%;   publisher = "Springer",
25030%; }
25031%;
25032%; model finding
25033%;
25034%; modifications from Shanahan's formulation:
25035%; InitiallyP -> HoldsAt
25036%; added [time] Terminates(Shoot(),Loaded(),time).
25037%; added !HoldsAt(Loaded(),0) to prune models
25038%; timestamps
25039%;
25040
25041% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8062
25042% load foundations/Root.e
25043
25044% load foundations/EC.e
25045
25046% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8065
25047% event Load()
25048 %  event(load()).
25049% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8066
25050==> mpred_prop(load(),event).
25051==> meta_argtypes(load()).
25052
25053% event Shoot()
25054 %  event(shoot()).
25055% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8067
25056==> mpred_prop(shoot(),event).
25057==> meta_argtypes(shoot()).
25058
25059% event Spin()
25060 %  event(spin()).
25061% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8068
25062==> mpred_prop(spin(),event).
25063==> meta_argtypes(spin()).
25064
25065% fluent Loaded()
25066 %  fluent(loaded()).
25067% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8069
25068==> mpred_prop(loaded(),fluent).
25069==> meta_argtypes(loaded()).
25070
25071% fluent Alive()
25072 %  fluent(alive()).
25073% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8070
25074==> mpred_prop(alive(),fluent).
25075==> meta_argtypes(alive()).
25076
25077
25078% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8071
25079% [time]
25080 % Initiates(Load(),Loaded(),time).
25081axiom(initiates(load(), loaded(), Time),
25082    []).
25083
25084
25085% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8072
25086% [time]
25087 % HoldsAt(Loaded(),time) -> Terminates(Shoot(),Alive(),time).
25088axiom(terminates(shoot(), alive(), Time),
25089    [holds_at(loaded(), Time)]).
25090
25091
25092% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8073
25093% [time]
25094 % Releases(Spin(),Loaded(),time).
25095axiom(releases(spin(), loaded(), Time),
25096    []).
25097
25098
25099% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8074
25100% [time]
25101 % Terminates(Shoot(),Loaded(),time).
25102axiom(terminates(shoot(), loaded(), Time),
25103    []).
25104
25105
25106% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8076
25107% HoldsAt(Alive(),0).
25108axiom(initially(alive()),
25109    []).
25110
25111
25112% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8077
25113% !HoldsAt(Loaded(),0).
25114 %  not(initially(loaded())).
25115axiom(not(initially(loaded())),
25116    []).
25117
25118
25119% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8078
25120% Happens(Load(),1).
25121axiom(happens(load(), start),
25122    [is_time(1), b(t, start), ignore(t+1=start)]).
25123
25124
25125% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8079
25126% Happens(Spin(),2).
25127axiom(happens(spin(), t2),
25128    [is_time(2), b(t, t2), ignore(t+2=t2)]).
25129
25130
25131% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8080
25132% Happens(Shoot(),3).
25133axiom(happens(shoot(), t3),
25134    [is_time(3), b(t, t3), ignore(t+3=t3)]).
25135
25136% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8082
25137% completion Happens
25138% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8083
25139==> completion(happens).
25140
25141% range time 0 4
25142% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8085
25143==> range(time,0,4).
25144
25145% range offset 1 1
25146% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8086
25147==> range(offset,1,1).
25148%; End of file.
25149%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25150%; FILE: examples/AkmanEtAl2004/ZooTest4.2.e
25151%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25152%;
25153%; Copyright (c) 2005 IBM Corporation and others.
25154%; All rights reserved. This program and the accompanying materials
25155%; are made available under the terms of the Common Public License v1.0
25156%; which accompanies this distribution, and is available at
25157%; http://www.eclipse.org/legal/cpl-v10.html
25158%;
25159%; Contributors:
25160%; IBM - Initial implementation
25161%;
25162%; @article{Akman:2004,
25163%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
25164%;   year = "2004",
25165%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
25166%;   journal = "Artificial Intelligence",
25167%;   volume = "153",
25168%;   pages = "105--140",
25169%; }
25170%;
25171
25172% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8114
25173% option encoding 3
25174% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8115
25175:- set_ec_option(encoding, 3).25176
25177% load foundations/Root.e
25178
25179% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8117
25180% load foundations/EC.e
25181
25182% load examples/AkmanEtAl2004/ZooWorld.e
25183
25184% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8120
25185% human Homer
25186% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8121
25187==> t(human,homer).
25188
25189% elephant Jumbo
25190% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8122
25191==> t(elephant,jumbo).
25192
25193
25194% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8123
25195% Species(Homer)=HumanSpecies.
25196species(homer,humanSpecies).
25197
25198
25199% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8124
25200% Adult(Homer).
25201adult(homer).
25202
25203
25204% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8125
25205% Species(Jumbo)=ElephantSpecies.
25206species(jumbo,elephantSpecies).
25207
25208
25209% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8126
25210% Adult(Jumbo).
25211adult(jumbo).
25212
25213
25214% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8128
25215% !HoldsAt(Opened(GateAO),0).
25216 %  not(initially(opened(gateAO))).
25217axiom(not(initially(opened(gateAO))),
25218    []).
25219% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8129
25220% {position} 
25221
25222
25223% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8129
25224% HoldsAt(Pos(Homer,position),0) & Outside=Loc(position).
25225
25226 /*   exists([Position],
25227              (holds_at(pos(homer, Position), 0), outside=loc(Position))).
25228 */
25229
25230 /*  not(some(Some_Param, '$kolem_Fn_371')) :-
25231       (   not(holds_at(pos(homer, Some_Param), 0))
25232       ;   not(equals(outside, loc(Some_Param)))
25233       ).
25234 */
25235axiom(not(some(Some_Param, '$kolem_Fn_371')),
25236    [not(holds_at(pos(homer, Some_Param), t))]).
25237axiom(not(some(Some_Param, '$kolem_Fn_371')),
25238    [not(equals(outside, loc(Some_Param)))]).
25239
25240 /*  holds_at(pos(homer, Some_Param3), 0) :-
25241       some(Some_Param3, '$kolem_Fn_371').
25242 */
25243axiom(holds_at(pos(homer, Some_Param3), t),
25244    [some(Some_Param3, '$kolem_Fn_371')]).
25245
25246 /*  equals(outside, loc(Some_Param4)) :-
25247       some(Some_Param4, '$kolem_Fn_371').
25248 */
25249axiom(equals(outside, loc(Some_Param4)),
25250    [some(Some_Param4, '$kolem_Fn_371')]).
25251% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8130
25252% {position} 
25253
25254
25255% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8130
25256% HoldsAt(Pos(Jumbo,position),0) & CageA=Loc(position).
25257
25258 /*   exists([Position],
25259              (holds_at(pos(jumbo, Position), 0), cageA=loc(Position))).
25260 */
25261
25262 /*  not(some(Some_Param, '$kolem_Fn_372')) :-
25263       (   not(holds_at(pos(jumbo, Some_Param), 0))
25264       ;   not(equals(cageA, loc(Some_Param)))
25265       ).
25266 */
25267axiom(not(some(Some_Param, '$kolem_Fn_372')),
25268    [not(holds_at(pos(jumbo, Some_Param), t))]).
25269axiom(not(some(Some_Param, '$kolem_Fn_372')),
25270    [not(equals(cageA, loc(Some_Param)))]).
25271
25272 /*  holds_at(pos(jumbo, Some_Param3), 0) :-
25273       some(Some_Param3, '$kolem_Fn_372').
25274 */
25275axiom(holds_at(pos(jumbo, Some_Param3), t),
25276    [some(Some_Param3, '$kolem_Fn_372')]).
25277
25278 /*  equals(cageA, loc(Some_Param4)) :-
25279       some(Some_Param4, '$kolem_Fn_372').
25280 */
25281axiom(equals(cageA, loc(Some_Param4)),
25282    [some(Some_Param4, '$kolem_Fn_372')]).
25283% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8132
25284% {position} 
25285
25286
25287% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8132
25288% HoldsAt(Pos(Homer,position),5) & CageA=Loc(position).
25289
25290 /*   exists([Position],
25291              (holds_at(pos(homer, Position), 5), cageA=loc(Position))).
25292 */
25293
25294 /*  not(some(Some_Param, '$kolem_Fn_373')) :-
25295       (   not(holds_at(pos(homer, Some_Param), 5))
25296       ;   not(equals(cageA, loc(Some_Param)))
25297       ).
25298 */
25299axiom(not(some(Some_Param, '$kolem_Fn_373')),
25300    [not(holds_at(pos(homer, Some_Param), t5)), b(t, t5), ignore(t+5=t5)]).
25301axiom(not(some(Some_Param, '$kolem_Fn_373')),
25302    [not(equals(cageA, loc(Some_Param)))]).
25303
25304 /*  holds_at(pos(homer, Some_Param3), 5) :-
25305       some(Some_Param3, '$kolem_Fn_373').
25306 */
25307axiom(holds_at(pos(homer, Some_Param3), t5),
25308    [some(Some_Param3, '$kolem_Fn_373'), b(t, t5), ignore(t+5=t5)]).
25309
25310 /*  equals(cageA, loc(Some_Param4)) :-
25311       some(Some_Param4, '$kolem_Fn_373').
25312 */
25313axiom(equals(cageA, loc(Some_Param4)),
25314    [some(Some_Param4, '$kolem_Fn_373')]).
25315% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8133
25316% {position} 
25317
25318
25319% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8133
25320% HoldsAt(Pos(Jumbo,position),5) & Outside=Loc(position).
25321
25322 /*   exists([Position],
25323              (holds_at(pos(jumbo, Position), 5), outside=loc(Position))).
25324 */
25325
25326 /*  not(some(Some_Param, '$kolem_Fn_374')) :-
25327       (   not(holds_at(pos(jumbo, Some_Param), 5))
25328       ;   not(equals(outside, loc(Some_Param)))
25329       ).
25330 */
25331axiom(not(some(Some_Param, '$kolem_Fn_374')),
25332    [not(holds_at(pos(jumbo, Some_Param), t5)), b(t, t5), ignore(t+5=t5)]).
25333axiom(not(some(Some_Param, '$kolem_Fn_374')),
25334    [not(equals(outside, loc(Some_Param)))]).
25335
25336 /*  holds_at(pos(jumbo, Some_Param3), 5) :-
25337       some(Some_Param3, '$kolem_Fn_374').
25338 */
25339axiom(holds_at(pos(jumbo, Some_Param3), t5),
25340    [some(Some_Param3, '$kolem_Fn_374'), b(t, t5), ignore(t+5=t5)]).
25341
25342 /*  equals(outside, loc(Some_Param4)) :-
25343       some(Some_Param4, '$kolem_Fn_374').
25344 */
25345axiom(equals(outside, loc(Some_Param4)),
25346    [some(Some_Param4, '$kolem_Fn_374')]).
25347
25348
25349% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8135
25350% [animal,time]
25351 % !HoldsAt(Mounted(Homer,animal),time).
25352 %  not(holds_at(mounted(homer,Animal),Time)).
25353axiom(not(holds_at(mounted(homer, Mounted_Ret), Time2)),
25354    []).
25355
25356
25357% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8137
25358% [human]
25359 % HoldsAt(PosDeterminingFluent(human,1),5).
25360holds_at(posDeterminingFluent(Human,1),5).
25361
25362
25363% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8138
25364% [event,animal]
25365 % !HoldsAt(DoneBy(event,animal),5).
25366 %  not(holds_at(doneBy(Event,Animal),5)).
25367axiom(not(holds_at(doneBy(DoneBy_Param, DoneBy_Ret), t5)),
25368    [b(t, t5), ignore(t+5=t5)]).
25369
25370
25371% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8140
25372%;HoldsAt(Pos(Homer,7),0).
25373%;HoldsAt(Pos(Jumbo,4),0).
25374%;Happens(Move(Jumbo,3),0).
25375%;Happens(Open(Homer,GateAO),0).
25376%;Happens(Move(Homer,4),1).
25377%;Happens(Move(Jumbo,1),1).
25378%;Happens(Move(Jumbo,3),2).
25379%;Happens(Mount(Homer,Jumbo),2).
25380%;Happens(Move(Jumbo,4),3).
25381%;!Happens(Move(Homer,2),3).
25382%;Happens(Move(Jumbo,7),4).
25383%;!Happens(Mount(Homer,Jumbo),3).
25384%;!Happens(Mount(Homer,Jumbo),4).
25385%;[position] !Happens(Move(Homer,position),4).
25386
25387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8155
25388% range time 0 5
25389% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8156
25390==> range(time,0,5).
25391
25392% range position 1 8
25393% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8157
25394==> range(position,1,8).
25395
25396% range offset 0 0
25397% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8158
25398==> range(offset,0,0).
25399
25400% completion Happens
25401% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8160
25402==> completion(happens).
25403%; End of file.
25404%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25405%; FILE: examples/AkmanEtAl2004/ZooTest5.1.e
25406%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25407%;
25408%; Copyright (c) 2005 IBM Corporation and others.
25409%; All rights reserved. This program and the accompanying materials
25410%; are made available under the terms of the Common Public License v1.0
25411%; which accompanies this distribution, and is available at
25412%; http://www.eclipse.org/legal/cpl-v10.html
25413%;
25414%; Contributors:
25415%; IBM - Initial implementation
25416%;
25417%; @article{Akman:2004,
25418%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
25419%;   year = "2004",
25420%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
25421%;   journal = "Artificial Intelligence",
25422%;   volume = "153",
25423%;   pages = "105--140",
25424%; }
25425%;
25426
25427% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8188
25428% option encoding 3
25429% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8189
25430:- set_ec_option(encoding, 3).25431
25432% load foundations/Root.e
25433
25434% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8191
25435% load foundations/EC.e
25436
25437% load examples/AkmanEtAl2004/ZooWorld.e
25438
25439% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8194
25440% human Homer
25441% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8195
25442==> t(human,homer).
25443
25444% elephant Jumbo
25445% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8196
25446==> t(elephant,jumbo).
25447
25448% horse Silver
25449% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8197
25450==> t(horse,silver).
25451
25452
25453% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8198
25454% Species(Homer)=HumanSpecies.
25455species(homer,humanSpecies).
25456
25457
25458% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8199
25459% Adult(Homer).
25460adult(homer).
25461
25462
25463% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8200
25464% Species(Jumbo)=ElephantSpecies.
25465species(jumbo,elephantSpecies).
25466
25467
25468% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8201
25469% Adult(Jumbo).
25470adult(jumbo).
25471
25472
25473% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8202
25474% Species(Silver)=HorseSpecies.
25475species(silver,horseSpecies).
25476
25477
25478% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8203
25479% Adult(Silver).
25480adult(silver).
25481% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8205
25482% {position}
25483
25484
25485% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8206
25486% !HoldsAt(Pos(Homer,position),0) &
25487% HoldsAt(Pos(Jumbo,position),0) &
25488% HoldsAt(Pos(Homer,position),1) &
25489% !HoldsAt(Pos(Jumbo,position),1).
25490
25491 /*   exists([Position],
25492              (not(holds_at(pos(homer, Position), 0)), holds_at(pos(jumbo, Position), 0), holds_at(pos(homer, Position), 1), not(holds_at(pos(jumbo, Position), 1)))).
25493 */
25494
25495 /*  not(some(Some_Param, '$kolem_Fn_375')) :-
25496       (   holds_at(pos(homer, Some_Param), 0)
25497       ;   not(holds_at(pos(jumbo, Some_Param), 0))
25498       ;   not(holds_at(pos(homer, Some_Param), 1))
25499       ;   holds_at(pos(jumbo, Some_Param), 1)
25500       ).
25501 */
25502% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8209
25503axiom(not(some(Some_Param, '$kolem_Fn_375')),
25504    [holds_at(pos(homer, Some_Param), t)]).
25505axiom(not(some(Some_Param, '$kolem_Fn_375')),
25506    [not(holds_at(pos(jumbo, Some_Param), t))]).
25507axiom(not(some(Some_Param, '$kolem_Fn_375')),
25508   
25509    [ not(holds_at(pos(homer, Some_Param), start)),
25510      b(t, start),
25511      ignore(t+1=start)
25512    ]).
25513axiom(not(some(Some_Param, '$kolem_Fn_375')),
25514    [holds_at(pos(jumbo, Some_Param), start), b(t, start), ignore(t+1=start)]).
25515
25516 /*  not(holds_at(pos(homer, Some_Param3), 0)) :-
25517       some(Some_Param3, '$kolem_Fn_375').
25518 */
25519axiom(not(holds_at(pos(homer, Some_Param3), t)),
25520    [some(Some_Param3, '$kolem_Fn_375')]).
25521
25522 /*  holds_at(pos(jumbo, Some_Param4), 0) :-
25523       some(Some_Param4, '$kolem_Fn_375').
25524 */
25525axiom(holds_at(pos(jumbo, Some_Param4), t),
25526    [some(Some_Param4, '$kolem_Fn_375')]).
25527
25528 /*  holds_at(pos(homer, Some_Param5), 1) :-
25529       some(Some_Param5, '$kolem_Fn_375').
25530 */
25531axiom(holds_at(pos(homer, Some_Param5), start),
25532    [some(Some_Param5, '$kolem_Fn_375'), b(t, start), ignore(t+1=start)]).
25533
25534 /*  not(holds_at(pos(jumbo, Some_Param6), 1)) :-
25535       some(Some_Param6, '$kolem_Fn_375').
25536 */
25537axiom(not(holds_at(pos(jumbo, Some_Param6), start)),
25538    [some(Some_Param6, '$kolem_Fn_375'), b(t, start), ignore(t+1=start)]).
25539
25540
25541% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8210
25542% HoldsAt(Mounted(Homer,Silver),0).
25543axiom(initially(mounted(homer, silver)),
25544    []).
25545
25546% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8212
25547% option manualrelease on
25548% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8213
25549:- set_ec_option(manualrelease, on).25550
25551
25552% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8213
25553% [human, animal]
25554 % !ReleasedAt(Mounted(human, animal),0).
25555 %  not(releasedAt(mounted(Human,Animal),0)).
25556axiom(not(releasedAt(mounted(Mounted_Param, Mounted_Ret), 0)),
25557    []).
25558
25559
25560% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8214
25561% [gate]
25562 % !ReleasedAt(Opened(gate),0).
25563 %  not(releasedAt(opened(Gate),0)).
25564axiom(not(releasedAt(opened(Opened_Ret), 0)),
25565    []).
25566
25567
25568% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8215
25569% [position]
25570 % ReleasedAt(Pos(Homer,position),0).
25571releasedAt(pos(homer,Position),0).
25572
25573
25574% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8216
25575% [position]
25576 % !ReleasedAt(Pos(Jumbo,position),0).
25577 %  not(releasedAt(pos(jumbo,Position),0)).
25578axiom(not(releasedAt(pos(jumbo, Pos_Ret), 0)),
25579    []).
25580
25581
25582% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8217
25583% [position]
25584 % !ReleasedAt(Pos(Silver,position),0).
25585 %  not(releasedAt(pos(silver,Position),0)).
25586axiom(not(releasedAt(pos(silver, Pos_Ret), 0)),
25587    []).
25588
25589
25590% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8219
25591% [human]
25592 % HoldsAt(PosDeterminingFluent(human,1),1).
25593holds_at(posDeterminingFluent(Human,1),1).
25594
25595
25596% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8220
25597% [event,animal]
25598 % !HoldsAt(DoneBy(event,animal),1).
25599 %  not(holds_at(doneBy(Event,Animal),1)).
25600axiom(not(holds_at(doneBy(DoneBy_Param, DoneBy_Ret), start)),
25601    [b(t, start), ignore(t+1=start)]).
25602
25603
25604% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8222
25605%;HoldsAt(Opened(GateAO),0).
25606%;HoldsAt(Pos(Homer,3),0).
25607%;HoldsAt(Pos(Jumbo,2),0).
25608%;HoldsAt(Pos(Silver,3),0).
25609%;Happens(Move(Jumbo,4),0).
25610%;Happens(ThrowOff(Silver,Homer),0).
25611%;HoldsAt(PosDeterminingFluent(Homer,2),0).
25612
25613% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8230
25614% range time 0 1
25615% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8231
25616==> range(time,0,1).
25617
25618% range position 1 8
25619% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8232
25620==> range(position,1,8).
25621
25622% range offset 0 0
25623% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8233
25624==> range(offset,0,0).
25625%; End of file.
25626%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25627%; FILE: examples/AkmanEtAl2004/ZooTest3.e
25628%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25629%;
25630%; Copyright (c) 2005 IBM Corporation and others.
25631%; All rights reserved. This program and the accompanying materials
25632%; are made available under the terms of the Common Public License v1.0
25633%; which accompanies this distribution, and is available at
25634%; http://www.eclipse.org/legal/cpl-v10.html
25635%;
25636%; Contributors:
25637%; IBM - Initial implementation
25638%;
25639%; @article{Akman:2004,
25640%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
25641%;   year = "2004",
25642%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
25643%;   journal = "Artificial Intelligence",
25644%;   volume = "153",
25645%;   pages = "105--140",
25646%; }
25647%;
25648
25649% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8261
25650% option encoding 3
25651% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8262
25652:- set_ec_option(encoding, 3).25653
25654% load foundations/Root.e
25655
25656% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8264
25657% load foundations/EC.e
25658
25659% load examples/AkmanEtAl2004/ZooWorld.e
25660
25661% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8267
25662% human Homer
25663% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8268
25664==> t(human,homer).
25665
25666% dog Snoopy
25667% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8269
25668==> t(dog,snoopy).
25669
25670
25671% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8270
25672% Species(Homer)=HumanSpecies.
25673species(homer,humanSpecies).
25674
25675
25676% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8271
25677% Adult(Homer).
25678adult(homer).
25679
25680
25681% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8272
25682% Species(Snoopy)=DogSpecies.
25683species(snoopy,dogSpecies).
25684
25685
25686% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8273
25687% Adult(Snoopy).
25688adult(snoopy).
25689
25690
25691% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8275
25692% !HoldsAt(Opened(GateAO),0).
25693 %  not(initially(opened(gateAO))).
25694axiom(not(initially(opened(gateAO))),
25695    []).
25696% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8276
25697% {position} 
25698
25699
25700% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8276
25701% HoldsAt(Pos(Homer,position),0) & Outside=Loc(position).
25702
25703 /*   exists([Position],
25704              (holds_at(pos(homer, Position), 0), outside=loc(Position))).
25705 */
25706
25707 /*  not(some(Some_Param, '$kolem_Fn_376')) :-
25708       (   not(holds_at(pos(homer, Some_Param), 0))
25709       ;   not(equals(outside, loc(Some_Param)))
25710       ).
25711 */
25712axiom(not(some(Some_Param, '$kolem_Fn_376')),
25713    [not(holds_at(pos(homer, Some_Param), t))]).
25714axiom(not(some(Some_Param, '$kolem_Fn_376')),
25715    [not(equals(outside, loc(Some_Param)))]).
25716
25717 /*  holds_at(pos(homer, Some_Param3), 0) :-
25718       some(Some_Param3, '$kolem_Fn_376').
25719 */
25720axiom(holds_at(pos(homer, Some_Param3), t),
25721    [some(Some_Param3, '$kolem_Fn_376')]).
25722
25723 /*  equals(outside, loc(Some_Param4)) :-
25724       some(Some_Param4, '$kolem_Fn_376').
25725 */
25726axiom(equals(outside, loc(Some_Param4)),
25727    [some(Some_Param4, '$kolem_Fn_376')]).
25728% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8277
25729% {position} 
25730
25731
25732% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8277
25733% HoldsAt(Pos(Snoopy,position),0) & CageA=Loc(position).
25734
25735 /*   exists([Position],
25736              (holds_at(pos(snoopy, Position), 0), cageA=loc(Position))).
25737 */
25738
25739 /*  not(some(Some_Param, '$kolem_Fn_377')) :-
25740       (   not(holds_at(pos(snoopy, Some_Param), 0))
25741       ;   not(equals(cageA, loc(Some_Param)))
25742       ).
25743 */
25744axiom(not(some(Some_Param, '$kolem_Fn_377')),
25745    [not(holds_at(pos(snoopy, Some_Param), t))]).
25746axiom(not(some(Some_Param, '$kolem_Fn_377')),
25747    [not(equals(cageA, loc(Some_Param)))]).
25748
25749 /*  holds_at(pos(snoopy, Some_Param3), 0) :-
25750       some(Some_Param3, '$kolem_Fn_377').
25751 */
25752axiom(holds_at(pos(snoopy, Some_Param3), t),
25753    [some(Some_Param3, '$kolem_Fn_377')]).
25754
25755 /*  equals(cageA, loc(Some_Param4)) :-
25756       some(Some_Param4, '$kolem_Fn_377').
25757 */
25758axiom(equals(cageA, loc(Some_Param4)),
25759    [some(Some_Param4, '$kolem_Fn_377')]).
25760% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8279
25761% {position} 
25762
25763
25764% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8279
25765% HoldsAt(Pos(Homer,position),2) & CageA=Loc(position).
25766
25767 /*   exists([Position],
25768              (holds_at(pos(homer, Position), 2), cageA=loc(Position))).
25769 */
25770
25771 /*  not(some(Some_Param, '$kolem_Fn_378')) :-
25772       (   not(holds_at(pos(homer, Some_Param), 2))
25773       ;   not(equals(cageA, loc(Some_Param)))
25774       ).
25775 */
25776axiom(not(some(Some_Param, '$kolem_Fn_378')),
25777    [not(holds_at(pos(homer, Some_Param), t2)), b(t, t2), ignore(t+2=t2)]).
25778axiom(not(some(Some_Param, '$kolem_Fn_378')),
25779    [not(equals(cageA, loc(Some_Param)))]).
25780
25781 /*  holds_at(pos(homer, Some_Param3), 2) :-
25782       some(Some_Param3, '$kolem_Fn_378').
25783 */
25784axiom(holds_at(pos(homer, Some_Param3), t2),
25785    [some(Some_Param3, '$kolem_Fn_378'), b(t, t2), ignore(t+2=t2)]).
25786
25787 /*  equals(cageA, loc(Some_Param4)) :-
25788       some(Some_Param4, '$kolem_Fn_378').
25789 */
25790axiom(equals(cageA, loc(Some_Param4)),
25791    [some(Some_Param4, '$kolem_Fn_378')]).
25792% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8280
25793% {position} 
25794
25795
25796% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8280
25797% HoldsAt(Pos(Snoopy,position),2) & Outside=Loc(position).
25798
25799 /*   exists([Position],
25800              (holds_at(pos(snoopy, Position), 2), outside=loc(Position))).
25801 */
25802
25803 /*  not(some(Some_Param, '$kolem_Fn_379')) :-
25804       (   not(holds_at(pos(snoopy, Some_Param), 2))
25805       ;   not(equals(outside, loc(Some_Param)))
25806       ).
25807 */
25808axiom(not(some(Some_Param, '$kolem_Fn_379')),
25809    [not(holds_at(pos(snoopy, Some_Param), t2)), b(t, t2), ignore(t+2=t2)]).
25810axiom(not(some(Some_Param, '$kolem_Fn_379')),
25811    [not(equals(outside, loc(Some_Param)))]).
25812
25813 /*  holds_at(pos(snoopy, Some_Param3), 2) :-
25814       some(Some_Param3, '$kolem_Fn_379').
25815 */
25816axiom(holds_at(pos(snoopy, Some_Param3), t2),
25817    [some(Some_Param3, '$kolem_Fn_379'), b(t, t2), ignore(t+2=t2)]).
25818
25819 /*  equals(outside, loc(Some_Param4)) :-
25820       some(Some_Param4, '$kolem_Fn_379').
25821 */
25822axiom(equals(outside, loc(Some_Param4)),
25823    [some(Some_Param4, '$kolem_Fn_379')]).
25824
25825
25826% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8282
25827% [human]
25828 % HoldsAt(PosDeterminingFluent(human,1),2).
25829holds_at(posDeterminingFluent(Human,1),2).
25830
25831
25832% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8283
25833% [event,animal]
25834 % !HoldsAt(DoneBy(event,animal),2).
25835 %  not(holds_at(doneBy(Event,Animal),2)).
25836axiom(not(holds_at(doneBy(DoneBy_Param, DoneBy_Ret), t2)),
25837    [b(t, t2), ignore(t+2=t2)]).
25838
25839% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8285
25840% range time 0 2
25841% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8286
25842==> range(time,0,2).
25843
25844% range position 1 8
25845% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8287
25846==> range(position,1,8).
25847
25848% range offset 0 0
25849% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8288
25850==> range(offset,0,0).
25851%; End of file.
25852%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25853%; FILE: examples/AkmanEtAl2004/ZooWorld.e
25854%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
25855%;
25856%; Copyright (c) 2005 IBM Corporation and others.
25857%; All rights reserved. This program and the accompanying materials
25858%; are made available under the terms of the Common Public License v1.0
25859%; which accompanies this distribution, and is available at
25860%; http://www.eclipse.org/legal/cpl-v10.html
25861%;
25862%; Contributors:
25863%; IBM - Initial implementation
25864%;
25865%; @article{Akman:2004,
25866%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
25867%;   year = "2004",
25868%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
25869%;   journal = "Artificial Intelligence",
25870%;   volume = "153",
25871%;   pages = "105--140",
25872%; }
25873%;
25874
25875% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8316
25876% sort position: integer
25877% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8317
25878==> subsort(position,integer).
25879
25880% sort location
25881% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8318
25882==> sort(location).
25883
25884% sort cage: location
25885% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8319
25886==> subsort(cage,location).
25887
25888% sort gate
25889% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8320
25890==> sort(gate).
25891
25892% sort animal
25893% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8321
25894==> sort(animal).
25895
25896% sort elephant: animal
25897% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8322
25898==> subsort(elephant,animal).
25899
25900% sort horse: animal
25901% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8323
25902==> subsort(horse,animal).
25903
25904% sort dog: animal
25905% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8324
25906==> subsort(dog,animal).
25907
25908% sort human: animal
25909% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8325
25910==> subsort(human,animal).
25911
25912% sort species
25913% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8326
25914==> sort(species).
25915
25916% function Loc(position): location
25917 %  functional_predicate(loc(position,location)).
25918% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8328
25919==> mpred_prop(loc(position,location),functional_predicate).
25920==> meta_argtypes(loc(position,location)).
25921resultIsa(loc,location).
25922
25923% function Side1(gate): position
25924 %  functional_predicate(side1(gate,position)).
25925% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8329
25926==> mpred_prop(side1(gate,position),functional_predicate).
25927==> meta_argtypes(side1(gate,position)).
25928resultIsa(side1,position).
25929
25930% function Side2(gate): position
25931 %  functional_predicate(side2(gate,position)).
25932% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8330
25933==> mpred_prop(side2(gate,position),functional_predicate).
25934==> meta_argtypes(side2(gate,position)).
25935resultIsa(side2,position).
25936
25937% function Species(animal): species
25938 %  functional_predicate(species(animal,species)).
25939% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8331
25940==> mpred_prop(species(animal,species),functional_predicate).
25941==> meta_argtypes(species(animal,species)).
25942resultIsa(species,species).
25943
25944% predicate Accessible(position,position,time)
25945 %  predicate(accessible(position,position,time)).
25946% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8333
25947==> mpred_prop(accessible(position,position,time),predicate).
25948==> meta_argtypes(accessible(position,position,time)).
25949
25950% predicate Adult(animal)
25951 %  predicate(adult(animal)).
25952% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8334
25953==> mpred_prop(adult(animal),predicate).
25954==> meta_argtypes(adult(animal)).
25955
25956% predicate Large(animal)
25957 %  predicate(large(animal)).
25958% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8335
25959==> mpred_prop(large(animal),predicate).
25960==> meta_argtypes(large(animal)).
25961
25962% predicate LargeSpecies(species)
25963 %  predicate(largeSpecies(species)).
25964% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8336
25965==> mpred_prop(largeSpecies(species),predicate).
25966==> meta_argtypes(largeSpecies(species)).
25967
25968% predicate Neighbor(position,position)
25969 %  predicate(neighbor(position,position)).
25970% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8337
25971==> mpred_prop(neighbor(position,position),predicate).
25972==> meta_argtypes(neighbor(position,position)).
25973
25974% predicate Sides(position,position,gate)
25975 %  predicate(sides(position,position,gate)).
25976% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8338
25977==> mpred_prop(sides(position,position,gate),predicate).
25978==> meta_argtypes(sides(position,position,gate)).
25979
25980% event Close(human,gate)
25981 %  event(close(human,gate)).
25982% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8340
25983==> mpred_prop(close(human,gate),event).
25984==> meta_argtypes(close(human,gate)).
25985
25986% event GetOff(human,animal)
25987 %  event(getOff(human,animal)).
25988% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8341
25989==> mpred_prop(getOff(human,animal),event).
25990==> meta_argtypes(getOff(human,animal)).
25991
25992% event Mount(human,animal)
25993 %  event(mount(human,animal)).
25994% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8342
25995==> mpred_prop(mount(human,animal),event).
25996==> meta_argtypes(mount(human,animal)).
25997
25998% event Move(animal,position)
25999 %  event(move(animal,position)).
26000% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8343
26001==> mpred_prop(move(animal,position),event).
26002==> meta_argtypes(move(animal,position)).
26003
26004% event Open(human,gate)
26005 %  event(open(human,gate)).
26006% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8344
26007==> mpred_prop(open(human,gate),event).
26008==> meta_argtypes(open(human,gate)).
26009
26010% event ThrowOff(animal,human)
26011 %  event(throwOff(animal,human)).
26012% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8345
26013==> mpred_prop(throwOff(animal,human),event).
26014==> meta_argtypes(throwOff(animal,human)).
26015
26016% fluent AbnormalEncroachment(human)
26017 %  fluent(abnormalEncroachment(human)).
26018% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8347
26019==> mpred_prop(abnormalEncroachment(human),fluent).
26020==> meta_argtypes(abnormalEncroachment(human)).
26021
26022% noninertial AbnormalEncroachment
26023% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8348
26024==> noninertial(abnormalEncroachment).
26025
26026% fluent DoneBy(event,animal)
26027 %  fluent(doneBy(event,animal)).
26028% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8349
26029==> mpred_prop(doneBy(event,animal),fluent).
26030==> meta_argtypes(doneBy(event,animal)).
26031
26032% noninertial DoneBy
26033% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8350
26034==> noninertial(doneBy).
26035
26036% fluent Mounted(human,animal)
26037 %  fluent(mounted(human,animal)).
26038% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8351
26039==> mpred_prop(mounted(human,animal),fluent).
26040==> meta_argtypes(mounted(human,animal)).
26041
26042% fluent MountFails(human)
26043 %  fluent(mountFails(human)).
26044% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8352
26045==> mpred_prop(mountFails(human),fluent).
26046==> meta_argtypes(mountFails(human)).
26047
26048% noninertial MountFails
26049% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8353
26050==> noninertial(mountFails).
26051
26052% fluent Moves(animal)
26053 %  fluent(moves(animal)).
26054% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8354
26055==> mpred_prop(moves(animal),fluent).
26056==> meta_argtypes(moves(animal)).
26057
26058% noninertial Moves
26059% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8355
26060==> noninertial(moves).
26061
26062% fluent Opened(gate)
26063 %  fluent(opened(gate)).
26064% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8356
26065==> mpred_prop(opened(gate),fluent).
26066==> meta_argtypes(opened(gate)).
26067
26068% fluent Pos(animal,position)
26069 %  fluent(pos(animal,position)).
26070% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8357
26071==> mpred_prop(pos(animal,position),fluent).
26072==> meta_argtypes(pos(animal,position)).
26073
26074% fluent PosDeterminingFluent(human,position)
26075 %  fluent(posDeterminingFluent(human,position)).
26076% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8358
26077==> mpred_prop(posDeterminingFluent(human,position),fluent).
26078==> meta_argtypes(posDeterminingFluent(human,position)).
26079
26080% noninertial PosDeterminingFluent
26081% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8359
26082==> noninertial(posDeterminingFluent).
26083
26084% fluent ThrowOffFails(animal,human)
26085 %  fluent(throwOffFails(animal,human)).
26086% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8360
26087==> mpred_prop(throwOffFails(animal,human),fluent).
26088==> meta_argtypes(throwOffFails(animal,human)).
26089
26090% noninertial ThrowOffFails
26091% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8361
26092==> noninertial(throwOffFails).
26093
26094% species HumanSpecies, ElephantSpecies, HorseSpecies, DogSpecies
26095% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8363
26096==> t(species,humanSpecies).
26097==> t(species,elephantSpecies).
26098==> t(species,horseSpecies).
26099==> t(species,dogSpecies).
26100
26101% location Outside
26102% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8364
26103==> t(location,outside).
26104
26105
26106% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8365
26107% LargeSpecies(HumanSpecies).
26108largeSpecies(humanSpecies).
26109
26110
26111% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8366
26112% LargeSpecies(ElephantSpecies).
26113largeSpecies(elephantSpecies).
26114
26115
26116% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8367
26117% LargeSpecies(HorseSpecies).
26118largeSpecies(horseSpecies).
26119
26120
26121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8368
26122% !LargeSpecies(DogSpecies).
26123 %  not(largeSpecies(dogSpecies)).
26124axiom(not(largeSpecies(dogSpecies)),
26125    []).
26126
26127
26128% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8370
26129% [event,animal,time]
26130% HoldsAt(DoneBy(event,animal),time) <->
26131% (Happens(event,time) &
26132%  (({gate} event=Close(animal,gate)) |
26133%   ({animal1} event=GetOff(animal,animal1))|
26134%   ({animal1} event=Mount(animal,animal1))|
26135%   ({position} event=Move(animal,position))|
26136%   ({gate} event=Open(animal,gate)) |
26137%   ({human1} event=ThrowOff(animal,human1)))).
26138
26139 /*  holds_at(doneBy(Event, Animal), Time) <->
26140       happens(Event, Time),
26141       (   exists([Gate], Event=close(Animal, Gate))
26142       ;   exists([Animal1], Event=getOff(Animal, Animal1))
26143       ;   exists([Animal15],
26144                  Event=mount(Animal, Animal15))
26145       ;   exists([Position], Event=move(Animal, Position))
26146       ;   exists([Gate7], Event=open(Animal, Gate7))
26147       ;   exists([Human1], Event=throwOff(Animal, Human1))
26148       ).
26149 */
26150% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8378
26151axiom(holds_at(doneBy(Event, Animal), Time),
26152   
26153    [ equals(Event, close(Animal, Gate)),
26154      happens(Event, Time)
26155    ]).
26156axiom(holds_at(doneBy(Event, Animal), Time),
26157   
26158    [ equals(Event, getOff(Animal, Animal1)),
26159      happens(Event, Time)
26160    ]).
26161axiom(holds_at(doneBy(Event, Animal), Time),
26162   
26163    [ equals(Event, mount(Animal, Animal15)),
26164      happens(Event, Time)
26165    ]).
26166axiom(holds_at(doneBy(Event, Animal), Time),
26167   
26168    [ equals(Event, move(Animal, Position)),
26169      happens(Event, Time)
26170    ]).
26171axiom(holds_at(doneBy(Event, Animal), Time),
26172   
26173    [ equals(Event, open(Animal, Gate7)),
26174      happens(Event, Time)
26175    ]).
26176axiom(holds_at(doneBy(Event, Animal), Time),
26177   
26178    [ equals(Event, throwOff(Animal, Human1)),
26179      happens(Event, Time)
26180    ]).
26181
26182 /*   if(holds_at(doneBy(Event, Animal), Time),
26183          (happens(Event, Time), (exists([Gate], Event=close(Animal, Gate));exists([Animal1], Event=getOff(Animal, Animal1));exists([Animal15], Event=mount(Animal, Animal15));exists([Position], Event=move(Animal, Position));exists([Gate7], Event=open(Animal, Gate7));exists([Human1], Event=throwOff(Animal, Human1))))).
26184 */
26185
26186 /*  not(holds_at(doneBy(DoneBy_Param, Close_Param), Time9)) :-
26187       (   not(happens(DoneBy_Param, Time9))
26188       ;   not(equals(DoneBy_Param,
26189                      close(Close_Param, Close_Ret))),
26190           not(equals(DoneBy_Param,
26191                      getOff(Close_Param, GetOff_Ret))),
26192           not(equals(DoneBy_Param,
26193                      mount(Close_Param, Mount_Ret))),
26194           not(equals(DoneBy_Param, move(Close_Param, Move_Ret))),
26195           not(equals(DoneBy_Param, open(Close_Param, Open_Ret))),
26196           not(equals(DoneBy_Param,
26197                      throwOff(Close_Param, ThrowOff_Ret)))
26198       ).
26199 */
26200axiom(not(holds_at(doneBy(DoneBy_Param, Close_Param), Time9)),
26201    [not(happens(DoneBy_Param, Time9))]).
26202axiom(not(holds_at(doneBy(DoneBy_Param, Close_Param), Time9)),
26203   
26204    [ not(equals(DoneBy_Param, close(Close_Param, Close_Ret))),
26205      not(equals(DoneBy_Param,
26206                 getOff(Close_Param, GetOff_Ret))),
26207      not(equals(DoneBy_Param, mount(Close_Param, Mount_Ret))),
26208      not(equals(DoneBy_Param, move(Close_Param, Move_Ret))),
26209      not(equals(DoneBy_Param, open(Close_Param, Open_Ret))),
26210      not(equals(DoneBy_Param,
26211                 throwOff(Close_Param, ThrowOff_Ret)))
26212    ]).
26213
26214 /*  happens(Happens_Param, Maptime) :-
26215       holds_at(doneBy(Happens_Param, DoneBy_Ret), Maptime).
26216 */
26217axiom(happens(Happens_Param, Maptime),
26218    [holds_at(doneBy(Happens_Param, DoneBy_Ret), Maptime)]).
26219
26220 /*  equals(Equals_Param, close(Close_Param23, Close_Ret24)) :-
26221       ( not(equals(Equals_Param,
26222                    getOff(Close_Param23, GetOff_Ret25))),
26223         not(equals(Equals_Param,
26224                    mount(Close_Param23, Mount_Ret26))),
26225         not(equals(Equals_Param,
26226                    move(Close_Param23, Move_Ret27))),
26227         not(equals(Equals_Param,
26228                    open(Close_Param23, Open_Ret28))),
26229         not(equals(Equals_Param,
26230                    throwOff(Close_Param23, ThrowOff_Ret29)))
26231       ),
26232       holds_at(doneBy(Equals_Param, Close_Param23), Time21).
26233 */
26234axiom(equals(Equals_Param, close(Close_Param23, Close_Ret24)),
26235   
26236    [ not(equals(Equals_Param,
26237                 getOff(Close_Param23, GetOff_Ret25))),
26238      not(equals(Equals_Param,
26239                 mount(Close_Param23, Mount_Ret26))),
26240      not(equals(Equals_Param,
26241                 move(Close_Param23, Move_Ret27))),
26242      not(equals(Equals_Param,
26243                 open(Close_Param23, Open_Ret28))),
26244      not(equals(Equals_Param,
26245                 throwOff(Close_Param23, ThrowOff_Ret29))),
26246      holds_at(doneBy(Equals_Param, Close_Param23), Time21)
26247    ]).
26248
26249 /*  equals(Equals_Param31, getOff(GetOff_Param, GetOff_Ret33)) :-
26250       ( not(equals(Equals_Param31,
26251                    mount(GetOff_Param, Mount_Ret34))),
26252         not(equals(Equals_Param31,
26253                    move(GetOff_Param, Move_Ret35))),
26254         not(equals(Equals_Param31,
26255                    open(GetOff_Param, Open_Ret36))),
26256         not(equals(Equals_Param31,
26257                    throwOff(GetOff_Param, ThrowOff_Ret37)))
26258       ),
26259       not(equals(Equals_Param31,
26260                  close(GetOff_Param, Close_Ret38))),
26261       holds_at(doneBy(Equals_Param31, GetOff_Param), Time30).
26262 */
26263axiom(equals(Equals_Param31, getOff(GetOff_Param, GetOff_Ret33)),
26264   
26265    [ not(equals(Equals_Param31,
26266                 mount(GetOff_Param, Mount_Ret34))),
26267      not(equals(Equals_Param31,
26268                 move(GetOff_Param, Move_Ret35))),
26269      not(equals(Equals_Param31,
26270                 open(GetOff_Param, Open_Ret36))),
26271      not(equals(Equals_Param31,
26272                 throwOff(GetOff_Param, ThrowOff_Ret37))),
26273      not(equals(Equals_Param31,
26274                 close(GetOff_Param, Close_Ret38))),
26275      holds_at(doneBy(Equals_Param31, GetOff_Param), Time30)
26276    ]).
26277
26278 /*  equals(Equals_Param40, mount(Mount_Param, Mount_Ret42)) :-
26279       ( not(equals(Equals_Param40,
26280                    move(Mount_Param, Move_Ret43))),
26281         not(equals(Equals_Param40,
26282                    open(Mount_Param, Open_Ret44))),
26283         not(equals(Equals_Param40,
26284                    throwOff(Mount_Param, ThrowOff_Ret45)))
26285       ),
26286       not(equals(Equals_Param40,
26287                  getOff(Mount_Param, GetOff_Ret46))),
26288       not(equals(Equals_Param40,
26289                  close(Mount_Param, Close_Ret47))),
26290       holds_at(doneBy(Equals_Param40, Mount_Param), Time39).
26291 */
26292axiom(equals(Equals_Param40, mount(Mount_Param, Mount_Ret42)),
26293   
26294    [ not(equals(Equals_Param40,
26295                 move(Mount_Param, Move_Ret43))),
26296      not(equals(Equals_Param40,
26297                 open(Mount_Param, Open_Ret44))),
26298      not(equals(Equals_Param40,
26299                 throwOff(Mount_Param, ThrowOff_Ret45))),
26300      not(equals(Equals_Param40,
26301                 getOff(Mount_Param, GetOff_Ret46))),
26302      not(equals(Equals_Param40,
26303                 close(Mount_Param, Close_Ret47))),
26304      holds_at(doneBy(Equals_Param40, Mount_Param), Time39)
26305    ]).
26306
26307 /*  equals(Equals_Param49, move(Move_Param, Move_Ret51)) :-
26308       ( not(equals(Equals_Param49, open(Move_Param, Open_Ret52))),
26309         not(equals(Equals_Param49,
26310                    throwOff(Move_Param, ThrowOff_Ret53)))
26311       ),
26312       not(equals(Equals_Param49, mount(Move_Param, Mount_Ret54))),
26313       not(equals(Equals_Param49,
26314                  getOff(Move_Param, GetOff_Ret55))),
26315       not(equals(Equals_Param49, close(Move_Param, Close_Ret56))),
26316       holds_at(doneBy(Equals_Param49, Move_Param), Time48).
26317 */
26318axiom(equals(Equals_Param49, move(Move_Param, Move_Ret51)),
26319   
26320    [ not(equals(Equals_Param49, open(Move_Param, Open_Ret52))),
26321      not(equals(Equals_Param49,
26322                 throwOff(Move_Param, ThrowOff_Ret53))),
26323      not(equals(Equals_Param49,
26324                 mount(Move_Param, Mount_Ret54))),
26325      not(equals(Equals_Param49,
26326                 getOff(Move_Param, GetOff_Ret55))),
26327      not(equals(Equals_Param49,
26328                 close(Move_Param, Close_Ret56))),
26329      holds_at(doneBy(Equals_Param49, Move_Param), Time48)
26330    ]).
26331
26332 /*  equals(Equals_Param58, open(Open_Param, Open_Ret60)) :-
26333       not(equals(Equals_Param58,
26334                  throwOff(Open_Param, ThrowOff_Ret61))),
26335       not(equals(Equals_Param58, move(Open_Param, Move_Ret62))),
26336       not(equals(Equals_Param58, mount(Open_Param, Mount_Ret63))),
26337       not(equals(Equals_Param58,
26338                  getOff(Open_Param, GetOff_Ret64))),
26339       not(equals(Equals_Param58, close(Open_Param, Close_Ret65))),
26340       holds_at(doneBy(Equals_Param58, Open_Param), Time57).
26341 */
26342axiom(equals(Equals_Param58, open(Open_Param, Open_Ret60)),
26343   
26344    [ not(equals(Equals_Param58,
26345                 throwOff(Open_Param, ThrowOff_Ret61))),
26346      not(equals(Equals_Param58, move(Open_Param, Move_Ret62))),
26347      not(equals(Equals_Param58,
26348                 mount(Open_Param, Mount_Ret63))),
26349      not(equals(Equals_Param58,
26350                 getOff(Open_Param, GetOff_Ret64))),
26351      not(equals(Equals_Param58,
26352                 close(Open_Param, Close_Ret65))),
26353      holds_at(doneBy(Equals_Param58, Open_Param), Time57)
26354    ]).
26355
26356 /*  equals(Equals_Param67, throwOff(ThrowOff_Param, ThrowOff_Ret69)) :-
26357       not(equals(Equals_Param67,
26358                  open(ThrowOff_Param, Open_Ret70))),
26359       not(equals(Equals_Param67,
26360                  move(ThrowOff_Param, Move_Ret71))),
26361       not(equals(Equals_Param67,
26362                  mount(ThrowOff_Param, Mount_Ret72))),
26363       not(equals(Equals_Param67,
26364                  getOff(ThrowOff_Param, GetOff_Ret73))),
26365       not(equals(Equals_Param67,
26366                  close(ThrowOff_Param, Close_Ret74))),
26367       holds_at(doneBy(Equals_Param67, ThrowOff_Param), Time66).
26368 */
26369axiom(equals(Equals_Param67, throwOff(ThrowOff_Param, ThrowOff_Ret69)),
26370   
26371    [ not(equals(Equals_Param67,
26372                 open(ThrowOff_Param, Open_Ret70))),
26373      not(equals(Equals_Param67,
26374                 move(ThrowOff_Param, Move_Ret71))),
26375      not(equals(Equals_Param67,
26376                 mount(ThrowOff_Param, Mount_Ret72))),
26377      not(equals(Equals_Param67,
26378                 getOff(ThrowOff_Param, GetOff_Ret73))),
26379      not(equals(Equals_Param67,
26380                 close(ThrowOff_Param, Close_Ret74))),
26381      holds_at(doneBy(Equals_Param67, ThrowOff_Param), Time66)
26382    ]).
26383
26384
26385% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8380
26386% [event1,event2,animal,time]
26387% HoldsAt(DoneBy(event1,animal),time) &
26388% HoldsAt(DoneBy(event2,animal),time) ->
26389% event1=event2.
26390% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8383
26391axiom(Event1=Event2,
26392   
26393    [ holds_at(doneBy(Event1, Animal), Time),
26394      holds_at(doneBy(Event2, Animal), Time)
26395    ]).
26396
26397
26398% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8385
26399% [animal]
26400 % Large(animal) <-> (Adult(animal) & LargeSpecies(Species(animal))).
26401
26402 /*  large(Animal) <->
26403       adult(Animal),
26404       largeSpecies(species(Animal)).
26405 */
26406axiom(large(Animal),
26407    [adult(Animal), largeSpecies(species(Animal))]).
26408
26409 /*   if(large(Animal),
26410          (adult(Animal), largeSpecies(species(Animal)))).
26411 */
26412
26413 /*  not(large(Large_Ret)) :-
26414       (   not(adult(Large_Ret))
26415       ;   not(largeSpecies(species(Large_Ret)))
26416       ).
26417 */
26418axiom(not(large(Large_Ret)),
26419    [not(adult(Large_Ret))]).
26420axiom(not(large(Large_Ret)),
26421    [not(largeSpecies(species(Large_Ret)))]).
26422
26423 /*  adult(Adult_Ret) :-
26424       large(Adult_Ret).
26425 */
26426axiom(adult(Adult_Ret),
26427    [large(Adult_Ret)]).
26428
26429 /*  largeSpecies(species(Species_Ret)) :-
26430       large(Species_Ret).
26431 */
26432axiom(largeSpecies(species(Species_Ret)),
26433    [large(Species_Ret)]).
26434
26435
26436% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8387
26437% [position]
26438 
26439% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8387
26440% {position1} % position1!=% position & Neighbor(position,position1).
26441
26442 /*   exists([Position1],
26443              (Position1\=Position, neighbor(Position, Position1))).
26444 */
26445
26446 /*  not(some(Some_Param, '$kolem_Fn_392'(Neighbor_Param))) :-
26447       (   not({dif(Some_Param, Neighbor_Param)})
26448       ;   not(neighbor(Neighbor_Param, Some_Param))
26449       ).
26450 */
26451axiom(not(some(Some_Param, '$kolem_Fn_392'(Neighbor_Param))),
26452    [not({dif(Some_Param, Neighbor_Param)})]).
26453axiom(not(some(Some_Param, '$kolem_Fn_392'(Neighbor_Param))),
26454    [not(neighbor(Neighbor_Param, Some_Param))]).
26455
26456 /*  { dif(Dif_Param, Dif_Ret)
26457   } :-
26458       some(Dif_Param, '$kolem_Fn_392'(Dif_Ret)).
26459 */
26460axiom({ dif(Dif_Param, Dif_Ret)
26461},
26462    [some(Dif_Param, '$kolem_Fn_392'(Dif_Ret))]).
26463
26464 /*  neighbor(Neighbor_Param7, Some_Param8) :-
26465       some(Some_Param8, '$kolem_Fn_392'(Neighbor_Param7)).
26466 */
26467axiom(neighbor(Neighbor_Param7, Some_Param8),
26468    [some(Some_Param8, '$kolem_Fn_392'(Neighbor_Param7))]).
26469
26470
26471% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8389
26472% [position]
26473 % !Neighbor(position,position).
26474 %  not(neighbor(Position,Position)).
26475axiom(not(neighbor(Neighbor_Param, Neighbor_Param)),
26476    []).
26477
26478
26479% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8391
26480% [position1,position2]
26481% Neighbor(position1,position2) ->
26482% Neighbor(position2,position1).
26483% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8393
26484axiom(neighbor(Position2, Position1),
26485    [neighbor(Position1, Position2)]).
26486
26487
26488% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8395
26489% [cage]
26490 % cage!=% Outside.
26491diff(Cage,outside).
26492
26493
26494% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8397
26495% [position1,position2,gate]
26496% Sides(position1,position2,gate) <->
26497% ((Side1(gate)=position1 &
26498%   Side2(gate)=position2) |
26499%  (Side2(gate)=position1 &
26500%   Side1(gate)=position2)).
26501
26502 /*  sides(Position1, Position2, Gate) <->
26503       (   side1(Gate)=Position1,
26504           side2(Gate)=Position2
26505       ;   side2(Gate)=Position1,
26506           side1(Gate)=Position2
26507       ).
26508 */
26509% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8402
26510axiom(sides(Position1, Position2, Gate),
26511   
26512    [ equals(side1(Gate), Position1),
26513      equals(side2(Gate), Position2)
26514    ]).
26515axiom(sides(Position1, Position2, Gate),
26516   
26517    [ equals(side2(Gate), Position1),
26518      equals(side1(Gate), Position2)
26519    ]).
26520
26521 /*   if(sides(Position1, Position2, Gate),
26522          (side1(Gate)=Position1, side2(Gate)=Position2;side2(Gate)=Position1, side1(Gate)=Position2)).
26523 */
26524
26525 /*  not(sides(Sides_Param, Equals_Ret, Sides_Ret)) :-
26526       (   not(equals(side1(Sides_Ret), Sides_Param))
26527       ;   not(equals(side2(Sides_Ret), Equals_Ret))
26528       ),
26529       (   not(equals(side2(Sides_Ret), Sides_Param))
26530       ;   not(equals(side1(Sides_Ret), Equals_Ret))
26531       ).
26532 */
26533axiom(not(sides(Sides_Param, Equals_Ret, Sides_Ret)),
26534   
26535    [ not(equals(side2(Sides_Ret), Sides_Param)),
26536      not(equals(side1(Sides_Ret), Sides_Param))
26537    ]).
26538axiom(not(sides(Sides_Param, Equals_Ret, Sides_Ret)),
26539   
26540    [ not(equals(side1(Sides_Ret), Equals_Ret)),
26541      not(equals(side1(Sides_Ret), Sides_Param))
26542    ]).
26543axiom(not(sides(Sides_Param, Equals_Ret, Sides_Ret)),
26544   
26545    [ not(equals(side2(Sides_Ret), Sides_Param)),
26546      not(equals(side2(Sides_Ret), Equals_Ret))
26547    ]).
26548axiom(not(sides(Sides_Param, Equals_Ret, Sides_Ret)),
26549   
26550    [ not(equals(side1(Sides_Ret), Equals_Ret)),
26551      not(equals(side2(Sides_Ret), Equals_Ret))
26552    ]).
26553
26554 /*  equals(side1(Side1_Ret), Sides_Param6) :-
26555       (   not(equals(side2(Side1_Ret), Sides_Param6))
26556       ;   not(equals(side1(Side1_Ret), Equals_Ret8))
26557       ),
26558       sides(Sides_Param6, Equals_Ret8, Side1_Ret).
26559 */
26560axiom(equals(side1(Side1_Ret), Sides_Param6),
26561   
26562    [ not(equals(side2(Side1_Ret), Sides_Param6)),
26563      sides(Sides_Param6, Equals_Ret8, Side1_Ret)
26564    ]).
26565axiom(equals(side1(Side1_Ret), Sides_Param6),
26566   
26567    [ not(equals(side1(Side1_Ret), Equals_Ret8)),
26568      sides(Sides_Param6, Equals_Ret8, Side1_Ret)
26569    ]).
26570
26571 /*  equals(side2(Side2_Ret), Equals_Ret10) :-
26572       (   not(equals(side2(Side2_Ret), Sides_Param9))
26573       ;   not(equals(side1(Side2_Ret), Equals_Ret10))
26574       ),
26575       sides(Sides_Param9, Equals_Ret10, Side2_Ret).
26576 */
26577axiom(equals(side2(Side2_Ret), Equals_Ret10),
26578   
26579    [ not(equals(side2(Side2_Ret), Sides_Param9)),
26580      sides(Sides_Param9, Equals_Ret10, Side2_Ret)
26581    ]).
26582axiom(equals(side2(Side2_Ret), Equals_Ret10),
26583   
26584    [ not(equals(side1(Side2_Ret), Equals_Ret10)),
26585      sides(Sides_Param9, Equals_Ret10, Side2_Ret)
26586    ]).
26587
26588 /*  equals(side2(Side2_Ret13), Sides_Param12) :-
26589       (   not(equals(side1(Side2_Ret13), Sides_Param12))
26590       ;   not(equals(side2(Side2_Ret13), Equals_Ret14))
26591       ),
26592       sides(Sides_Param12, Equals_Ret14, Side2_Ret13).
26593 */
26594axiom(equals(side2(Side2_Ret13), Sides_Param12),
26595   
26596    [ not(equals(side1(Side2_Ret13), Sides_Param12)),
26597      sides(Sides_Param12, Equals_Ret14, Side2_Ret13)
26598    ]).
26599axiom(equals(side2(Side2_Ret13), Sides_Param12),
26600   
26601    [ not(equals(side2(Side2_Ret13), Equals_Ret14)),
26602      sides(Sides_Param12, Equals_Ret14, Side2_Ret13)
26603    ]).
26604
26605 /*  equals(side1(Side1_Ret17), Equals_Ret16) :-
26606       (   not(equals(side1(Side1_Ret17), Sides_Param15))
26607       ;   not(equals(side2(Side1_Ret17), Equals_Ret16))
26608       ),
26609       sides(Sides_Param15, Equals_Ret16, Side1_Ret17).
26610 */
26611axiom(equals(side1(Side1_Ret17), Equals_Ret16),
26612   
26613    [ not(equals(side1(Side1_Ret17), Sides_Param15)),
26614      sides(Sides_Param15, Equals_Ret16, Side1_Ret17)
26615    ]).
26616axiom(equals(side1(Side1_Ret17), Equals_Ret16),
26617   
26618    [ not(equals(side2(Side1_Ret17), Equals_Ret16)),
26619      sides(Sides_Param15, Equals_Ret16, Side1_Ret17)
26620    ]).
26621
26622
26623% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8404
26624% [gate]
26625 % Loc(Side1(gate))!=Loc(Side2(gate)).
26626diff(loc(side1(Gate)),loc(side2(Gate))).
26627
26628
26629% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8406
26630% [position1,position2,gate1,gate2]
26631% Sides(position1,position2,gate1) &
26632% Sides(position1,position2,gate2) ->
26633% gate1=gate2.
26634% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8409
26635axiom(Gate1=Gate2,
26636   
26637    [ sides(Position1, Position2, Gate1),
26638      sides(Position1, Position2, Gate2)
26639    ]).
26640
26641
26642% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8411
26643% [position1,position2,gate]
26644% Sides(position1,position2,gate) ->
26645% Neighbor(position1,position2).
26646% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8413
26647axiom(neighbor(Position1, Position2),
26648    [sides(Position1, Position2, Gate)]).
26649
26650
26651% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8415
26652% [position1,position2]
26653% Loc(position1) != Loc(position2) &
26654% Neighbor(position1,position2) ->
26655% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8418
26656% {gate}%  Sides(position1,position2,gate).
26657
26658 /*   exists([Gate],
26659             if((loc(Position1)\=loc(Position2), neighbor(Position1, Position2)),
26660                sides(Position1, Position2, Gate))).
26661 */
26662
26663 /*  sides(Sides_Param, Loc_Ret, Some_Param) :-
26664       ( { dif(loc(Sides_Param), loc(Loc_Ret))
26665         },
26666         neighbor(Sides_Param, Loc_Ret)
26667       ),
26668       some(Some_Param, '$kolem_Fn_393'(Sides_Param, Loc_Ret)).
26669 */
26670axiom(sides(Sides_Param, Loc_Ret, Some_Param),
26671   
26672    [ { dif(loc(Sides_Param), loc(Loc_Ret))
26673      },
26674      neighbor(Sides_Param, Loc_Ret),
26675      some(Some_Param, '$kolem_Fn_393'(Sides_Param, Loc_Ret))
26676    ]).
26677
26678 /*  not({dif(loc(Neighbor_Param), loc(Loc_Ret9))}) :-
26679       neighbor(Neighbor_Param, Loc_Ret9),
26680       not(sides(Neighbor_Param, Loc_Ret9, Some_Param8)),
26681       some(Some_Param8, '$kolem_Fn_393'(Neighbor_Param, Loc_Ret9)).
26682 */
26683axiom(not({dif(loc(Neighbor_Param), loc(Loc_Ret9))}),
26684   
26685    [ neighbor(Neighbor_Param, Loc_Ret9),
26686      not(sides(Neighbor_Param, Loc_Ret9, Some_Param8)),
26687      some(Some_Param8,
26688           '$kolem_Fn_393'(Neighbor_Param, Loc_Ret9))
26689    ]).
26690
26691 /*  not(neighbor(Neighbor_Param10, Neighbor_Ret)) :-
26692       { dif(loc(Neighbor_Param10), loc(Neighbor_Ret))
26693       },
26694       not(sides(Neighbor_Param10, Neighbor_Ret, Some_Param11)),
26695       some(Some_Param11,
26696            '$kolem_Fn_393'(Neighbor_Param10, Neighbor_Ret)).
26697 */
26698axiom(not(neighbor(Neighbor_Param10, Neighbor_Ret)),
26699   
26700    [ { dif(loc(Neighbor_Param10), loc(Neighbor_Ret))
26701      },
26702      not(sides(Neighbor_Param10, Neighbor_Ret, Some_Param11)),
26703      some(Some_Param11,
26704           '$kolem_Fn_393'(Neighbor_Param10, Neighbor_Ret))
26705    ]).
26706
26707 /*  not(some(Some_Param13, '$kolem_Fn_393'(Fn_393_Param, Fn_393_Ret))) :-
26708       not(sides(Fn_393_Param, Fn_393_Ret, Some_Param13)),
26709       { dif(loc(Fn_393_Param), loc(Fn_393_Ret))
26710       },
26711       neighbor(Fn_393_Param, Fn_393_Ret).
26712 */
26713axiom(not(some(Some_Param13, '$kolem_Fn_393'(Fn_393_Param, Fn_393_Ret))),
26714   
26715    [ not(sides(Fn_393_Param, Fn_393_Ret, Some_Param13)),
26716      { dif(loc(Fn_393_Param), loc(Fn_393_Ret))
26717      },
26718      neighbor(Fn_393_Param, Fn_393_Ret)
26719    ]).
26720
26721
26722% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8420
26723% [animal,position1,position2,time]
26724% HoldsAt(Pos(animal,position1),time) &
26725% HoldsAt(Pos(animal,position2),time) ->
26726% position1=position2.
26727% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8423
26728axiom(Position1=Position2,
26729   
26730    [ holds_at(pos(Animal, Position1), Time),
26731      holds_at(pos(Animal, Position2), Time)
26732    ]).
26733
26734
26735% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8425
26736% [animal,time]
26737% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8426
26738% {position} % HoldsAt(Pos(animal,position),time).
26739
26740 /*  exists([Position],
26741          holds_at(pos(Animal,Position),Time)).
26742 */
26743
26744 /*  holds_at(pos(Pos_Param, Some_Param), Time4) :-
26745       some(Some_Param, '$kolem_Fn_394'(Pos_Param, Time4)).
26746 */
26747axiom(holds_at(pos(Pos_Param, Some_Param), Time4),
26748    [some(Some_Param, '$kolem_Fn_394'(Pos_Param, Time4))]).
26749
26750 /*  not(some(Some_Param8, '$kolem_Fn_394'(Fn_394_Param, Time7))) :-
26751       not(holds_at(pos(Fn_394_Param, Some_Param8), Time7)).
26752 */
26753axiom(not(some(Some_Param8, '$kolem_Fn_394'(Fn_394_Param, Time7))),
26754    [not(holds_at(pos(Fn_394_Param, Some_Param8), Time7))]).
26755
26756
26757% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8428
26758% [animal1,animal2,position,time]
26759% (animal1!=animal2 &
26760%  Large(animal1) &
26761%  Large(animal2) &
26762%  HoldsAt(Pos(animal1,position),time) &
26763%  HoldsAt(Pos(animal2,position),time)) ->
26764% (({human} human=animal1 & HoldsAt(Mounted(human,animal2),time)) |
26765%  ({human} human=animal2 & HoldsAt(Mounted(human,animal1),time))).
26766
26767 /*   if(({dif(Animal1, Animal2)}, large(Animal1), large(Animal2), holds_at(pos(Animal1, Position), Time), holds_at(pos(Animal2, Position), Time)),
26768          (exists([Human],  (Human=Animal1, holds_at(mounted(Human, Animal2), Time)));exists([Human5],  (Human5=Animal2, holds_at(mounted(Human5, Animal1), Time))))).
26769 */
26770
26771 /*  not({dif(Dif_Param, Pos_Param)}) :-
26772       ( large(Dif_Param),
26773         large(Pos_Param),
26774         holds_at(pos(Dif_Param, Pos_Ret), Time6),
26775         holds_at(pos(Pos_Param, Pos_Ret), Time6)
26776       ),
26777       (   not(equals(Equals_Param, Dif_Param))
26778       ;   not(holds_at(mounted(Equals_Param, Pos_Param), Time6))
26779       ),
26780       (   not(equals(Equals_Param10, Pos_Param))
26781       ;   not(holds_at(mounted(Equals_Param10, Dif_Param),
26782                        Time6))
26783       ).
26784 */
26785% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8435
26786axiom(not({dif(Dif_Param, Pos_Param)}),
26787   
26788    [ not(equals(Equals_Param10, Pos_Param)),
26789      not(equals(Equals_Param, Dif_Param)),
26790      large(Dif_Param),
26791      large(Pos_Param),
26792      holds_at(pos(Dif_Param, Pos_Ret), Time6),
26793      holds_at(pos(Pos_Param, Pos_Ret), Time6)
26794    ]).
26795axiom(not({dif(Dif_Param, Pos_Param)}),
26796   
26797    [ not(holds_at(mounted(Equals_Param10, Dif_Param), Time6)),
26798      not(equals(Equals_Param, Dif_Param)),
26799      large(Dif_Param),
26800      large(Pos_Param),
26801      holds_at(pos(Dif_Param, Pos_Ret), Time6),
26802      holds_at(pos(Pos_Param, Pos_Ret), Time6)
26803    ]).
26804axiom(not({dif(Dif_Param, Pos_Param)}),
26805   
26806    [ not(equals(Equals_Param10, Pos_Param)),
26807      not(holds_at(mounted(Equals_Param, Pos_Param), Time6)),
26808      large(Dif_Param),
26809      large(Pos_Param),
26810      holds_at(pos(Dif_Param, Pos_Ret), Time6),
26811      holds_at(pos(Pos_Param, Pos_Ret), Time6)
26812    ]).
26813axiom(not({dif(Dif_Param, Pos_Param)}),
26814   
26815    [ not(holds_at(mounted(Equals_Param10, Dif_Param), Time6)),
26816      not(holds_at(mounted(Equals_Param, Pos_Param), Time6)),
26817      large(Dif_Param),
26818      large(Pos_Param),
26819      holds_at(pos(Dif_Param, Pos_Ret), Time6),
26820      holds_at(pos(Pos_Param, Pos_Ret), Time6)
26821    ]).
26822
26823 /*  not(large(Pos_Param13)) :-
26824       ( large(Pos_Param14),
26825         holds_at(pos(Pos_Param13, Pos_Ret17), Time12),
26826         holds_at(pos(Pos_Param14, Pos_Ret17), Time12)
26827       ),
26828       { dif(Pos_Param13, Pos_Param14)
26829       },
26830       (   not(equals(Equals_Param15, Pos_Param13))
26831       ;   not(holds_at(mounted(Equals_Param15, Pos_Param14),
26832                        Time12))
26833       ),
26834       (   not(equals(Equals_Param16, Pos_Param14))
26835       ;   not(holds_at(mounted(Equals_Param16, Pos_Param13),
26836                        Time12))
26837       ).
26838 */
26839axiom(not(large(Pos_Param13)),
26840   
26841    [ not(equals(Equals_Param16, Pos_Param14)),
26842      not(equals(Equals_Param15, Pos_Param13)),
26843      large(Pos_Param14),
26844      holds_at(pos(Pos_Param13, Pos_Ret17), Time12),
26845      holds_at(pos(Pos_Param14, Pos_Ret17), Time12),
26846      { dif(Pos_Param13, Pos_Param14)
26847      }
26848    ]).
26849axiom(not(large(Pos_Param13)),
26850   
26851    [ not(holds_at(mounted(Equals_Param16, Pos_Param13),
26852                   Time12)),
26853      not(equals(Equals_Param15, Pos_Param13)),
26854      large(Pos_Param14),
26855      holds_at(pos(Pos_Param13, Pos_Ret17), Time12),
26856      holds_at(pos(Pos_Param14, Pos_Ret17), Time12),
26857      { dif(Pos_Param13, Pos_Param14)
26858      }
26859    ]).
26860axiom(not(large(Pos_Param13)),
26861   
26862    [ not(equals(Equals_Param16, Pos_Param14)),
26863      not(holds_at(mounted(Equals_Param15, Pos_Param14),
26864                   Time12)),
26865      large(Pos_Param14),
26866      holds_at(pos(Pos_Param13, Pos_Ret17), Time12),
26867      holds_at(pos(Pos_Param14, Pos_Ret17), Time12),
26868      { dif(Pos_Param13, Pos_Param14)
26869      }
26870    ]).
26871axiom(not(large(Pos_Param13)),
26872   
26873    [ not(holds_at(mounted(Equals_Param16, Pos_Param13),
26874                   Time12)),
26875      not(holds_at(mounted(Equals_Param15, Pos_Param14),
26876                   Time12)),
26877      large(Pos_Param14),
26878      holds_at(pos(Pos_Param13, Pos_Ret17), Time12),
26879      holds_at(pos(Pos_Param14, Pos_Ret17), Time12),
26880      { dif(Pos_Param13, Pos_Param14)
26881      }
26882    ]).
26883
26884 /*  not(large(Pos_Param20)) :-
26885       ( holds_at(pos(Pos_Param19, Pos_Ret23), Time18),
26886         holds_at(pos(Pos_Param20, Pos_Ret23), Time18)
26887       ),
26888       large(Pos_Param19),
26889       { dif(Pos_Param19, Pos_Param20)
26890       },
26891       (   not(equals(Equals_Param21, Pos_Param19))
26892       ;   not(holds_at(mounted(Equals_Param21, Pos_Param20),
26893                        Time18))
26894       ),
26895       (   not(equals(Equals_Param22, Pos_Param20))
26896       ;   not(holds_at(mounted(Equals_Param22, Pos_Param19),
26897                        Time18))
26898       ).
26899 */
26900axiom(not(large(Pos_Param20)),
26901   
26902    [ not(equals(Equals_Param22, Pos_Param20)),
26903      not(equals(Equals_Param21, Pos_Param19)),
26904      holds_at(pos(Pos_Param19, Pos_Ret23), Time18),
26905      holds_at(pos(Pos_Param20, Pos_Ret23), Time18),
26906      large(Pos_Param19),
26907      { dif(Pos_Param19, Pos_Param20)
26908      }
26909    ]).
26910axiom(not(large(Pos_Param20)),
26911   
26912    [ not(holds_at(mounted(Equals_Param22, Pos_Param19),
26913                   Time18)),
26914      not(equals(Equals_Param21, Pos_Param19)),
26915      holds_at(pos(Pos_Param19, Pos_Ret23), Time18),
26916      holds_at(pos(Pos_Param20, Pos_Ret23), Time18),
26917      large(Pos_Param19),
26918      { dif(Pos_Param19, Pos_Param20)
26919      }
26920    ]).
26921axiom(not(large(Pos_Param20)),
26922   
26923    [ not(equals(Equals_Param22, Pos_Param20)),
26924      not(holds_at(mounted(Equals_Param21, Pos_Param20),
26925                   Time18)),
26926      holds_at(pos(Pos_Param19, Pos_Ret23), Time18),
26927      holds_at(pos(Pos_Param20, Pos_Ret23), Time18),
26928      large(Pos_Param19),
26929      { dif(Pos_Param19, Pos_Param20)
26930      }
26931    ]).
26932axiom(not(large(Pos_Param20)),
26933   
26934    [ not(holds_at(mounted(Equals_Param22, Pos_Param19),
26935                   Time18)),
26936      not(holds_at(mounted(Equals_Param21, Pos_Param20),
26937                   Time18)),
26938      holds_at(pos(Pos_Param19, Pos_Ret23), Time18),
26939      holds_at(pos(Pos_Param20, Pos_Ret23), Time18),
26940      large(Pos_Param19),
26941      { dif(Pos_Param19, Pos_Param20)
26942      }
26943    ]).
26944
26945 /*  not(holds_at(pos(Pos_Param25, Pos_Ret29), Time24)) :-
26946       holds_at(pos(Pos_Param26, Pos_Ret29), Time24),
26947       large(Pos_Param26),
26948       large(Pos_Param25),
26949       { dif(Pos_Param25, Pos_Param26)
26950       },
26951       (   not(equals(Equals_Param27, Pos_Param25))
26952       ;   not(holds_at(mounted(Equals_Param27, Pos_Param26),
26953                        Time24))
26954       ),
26955       (   not(equals(Equals_Param28, Pos_Param26))
26956       ;   not(holds_at(mounted(Equals_Param28, Pos_Param25),
26957                        Time24))
26958       ).
26959 */
26960axiom(not(holds_at(pos(Pos_Param25, Pos_Ret29), Time24)),
26961   
26962    [ not(equals(Equals_Param28, Pos_Param26)),
26963      not(equals(Equals_Param27, Pos_Param25)),
26964      holds_at(pos(Pos_Param26, Pos_Ret29), Time24),
26965      large(Pos_Param26),
26966      large(Pos_Param25),
26967      dif(Pos_Param25, Pos_Param26)
26968    ]).
26969axiom(not(holds_at(pos(Pos_Param25, Pos_Ret29), Time24)),
26970   
26971    [ not(holds_at(mounted(Equals_Param28, Pos_Param25),
26972                   Time24)),
26973      not(equals(Equals_Param27, Pos_Param25)),
26974      holds_at(pos(Pos_Param26, Pos_Ret29), Time24),
26975      large(Pos_Param26),
26976      large(Pos_Param25),
26977      dif(Pos_Param25, Pos_Param26)
26978    ]).
26979axiom(not(holds_at(pos(Pos_Param25, Pos_Ret29), Time24)),
26980   
26981    [ not(equals(Equals_Param28, Pos_Param26)),
26982      not(holds_at(mounted(Equals_Param27, Pos_Param26),
26983                   Time24)),
26984      holds_at(pos(Pos_Param26, Pos_Ret29), Time24),
26985      large(Pos_Param26),
26986      large(Pos_Param25),
26987      dif(Pos_Param25, Pos_Param26)
26988    ]).
26989axiom(not(holds_at(pos(Pos_Param25, Pos_Ret29), Time24)),
26990   
26991    [ not(holds_at(mounted(Equals_Param28, Pos_Param25),
26992                   Time24)),
26993      not(holds_at(mounted(Equals_Param27, Pos_Param26),
26994                   Time24)),
26995      holds_at(pos(Pos_Param26, Pos_Ret29), Time24),
26996      large(Pos_Param26),
26997      large(Pos_Param25),
26998      dif(Pos_Param25, Pos_Param26)
26999    ]).
27000
27001 /*  not(holds_at(pos(Pos_Param31, Pos_Ret35), Time30)) :-
27002       holds_at(pos(Pos_Param32, Pos_Ret35), Time30),
27003       large(Pos_Param31),
27004       large(Pos_Param32),
27005       { dif(Pos_Param32, Pos_Param31)
27006       },
27007       (   not(equals(Equals_Param33, Pos_Param32))
27008       ;   not(holds_at(mounted(Equals_Param33, Pos_Param31),
27009                        Time30))
27010       ),
27011       (   not(equals(Equals_Param34, Pos_Param31))
27012       ;   not(holds_at(mounted(Equals_Param34, Pos_Param32),
27013                        Time30))
27014       ).
27015 */
27016axiom(not(holds_at(pos(Pos_Param31, Pos_Ret35), Time30)),
27017   
27018    [ not(equals(Equals_Param34, Pos_Param31)),
27019      not(equals(Equals_Param33, Pos_Param32)),
27020      holds_at(pos(Pos_Param32, Pos_Ret35), Time30),
27021      large(Pos_Param31),
27022      large(Pos_Param32),
27023      dif(Pos_Param32, Pos_Param31)
27024    ]).
27025axiom(not(holds_at(pos(Pos_Param31, Pos_Ret35), Time30)),
27026   
27027    [ not(holds_at(mounted(Equals_Param34, Pos_Param32),
27028                   Time30)),
27029      not(equals(Equals_Param33, Pos_Param32)),
27030      holds_at(pos(Pos_Param32, Pos_Ret35), Time30),
27031      large(Pos_Param31),
27032      large(Pos_Param32),
27033      dif(Pos_Param32, Pos_Param31)
27034    ]).
27035axiom(not(holds_at(pos(Pos_Param31, Pos_Ret35), Time30)),
27036   
27037    [ not(equals(Equals_Param34, Pos_Param31)),
27038      not(holds_at(mounted(Equals_Param33, Pos_Param31),
27039                   Time30)),
27040      holds_at(pos(Pos_Param32, Pos_Ret35), Time30),
27041      large(Pos_Param31),
27042      large(Pos_Param32),
27043      dif(Pos_Param32, Pos_Param31)
27044    ]).
27045axiom(not(holds_at(pos(Pos_Param31, Pos_Ret35), Time30)),
27046   
27047    [ not(holds_at(mounted(Equals_Param34, Pos_Param32),
27048                   Time30)),
27049      not(holds_at(mounted(Equals_Param33, Pos_Param31),
27050                   Time30)),
27051      holds_at(pos(Pos_Param32, Pos_Ret35), Time30),
27052      large(Pos_Param31),
27053      large(Pos_Param32),
27054      dif(Pos_Param32, Pos_Param31)
27055    ]).
27056
27057 /*  equals(Equals_Param37, Dif_Param39) :-
27058       (   not(equals(Equals_Param38, Pos_Param40))
27059       ;   not(holds_at(mounted(Equals_Param38, Dif_Param39),
27060                        Time36))
27061       ),
27062       { dif(Dif_Param39, Pos_Param40)
27063       },
27064       large(Dif_Param39),
27065       large(Pos_Param40),
27066       holds_at(pos(Dif_Param39, Pos_Ret41), Time36),
27067       holds_at(pos(Pos_Param40, Pos_Ret41), Time36).
27068 */
27069axiom(equals(Equals_Param37, Dif_Param39),
27070   
27071    [ not(equals(Equals_Param38, Pos_Param40)),
27072      { dif(Dif_Param39, Pos_Param40)
27073      },
27074      large(Dif_Param39),
27075      large(Pos_Param40),
27076      holds_at(pos(Dif_Param39, Pos_Ret41), Time36),
27077      holds_at(pos(Pos_Param40, Pos_Ret41), Time36)
27078    ]).
27079axiom(equals(Equals_Param37, Dif_Param39),
27080   
27081    [ not(holds_at(mounted(Equals_Param38, Dif_Param39),
27082                   Time36)),
27083      { dif(Dif_Param39, Pos_Param40)
27084      },
27085      large(Dif_Param39),
27086      large(Pos_Param40),
27087      holds_at(pos(Dif_Param39, Pos_Ret41), Time36),
27088      holds_at(pos(Pos_Param40, Pos_Ret41), Time36)
27089    ]).
27090
27091 /*  holds_at(mounted(Mounted_Param, Pos_Param46), Time42) :-
27092       (   not(equals(Equals_Param44, Pos_Param46))
27093       ;   not(holds_at(mounted(Equals_Param44, Dif_Param45),
27094                        Time42))
27095       ),
27096       { dif(Dif_Param45, Pos_Param46)
27097       },
27098       large(Dif_Param45),
27099       large(Pos_Param46),
27100       holds_at(pos(Dif_Param45, Pos_Ret47), Time42),
27101       holds_at(pos(Pos_Param46, Pos_Ret47), Time42).
27102 */
27103axiom(holds_at(mounted(Mounted_Param, Pos_Param46), Time42),
27104   
27105    [ not(equals(Equals_Param44, Pos_Param46)),
27106      dif(Dif_Param45, Pos_Param46),
27107      large(Dif_Param45),
27108      large(Pos_Param46),
27109      holds_at(pos(Dif_Param45, Pos_Ret47), Time42),
27110      holds_at(pos(Pos_Param46, Pos_Ret47), Time42)
27111    ]).
27112axiom(holds_at(mounted(Mounted_Param, Pos_Param46), Time42),
27113   
27114    [ not(holds_at(mounted(Equals_Param44, Dif_Param45),
27115                   Time42)),
27116      dif(Dif_Param45, Pos_Param46),
27117      large(Dif_Param45),
27118      large(Pos_Param46),
27119      holds_at(pos(Dif_Param45, Pos_Ret47), Time42),
27120      holds_at(pos(Pos_Param46, Pos_Ret47), Time42)
27121    ]).
27122
27123 /*  equals(Equals_Param49, Pos_Param52) :-
27124       (   not(equals(Equals_Param50, Dif_Param51))
27125       ;   not(holds_at(mounted(Equals_Param50, Pos_Param52),
27126                        Time48))
27127       ),
27128       { dif(Dif_Param51, Pos_Param52)
27129       },
27130       large(Dif_Param51),
27131       large(Pos_Param52),
27132       holds_at(pos(Dif_Param51, Pos_Ret53), Time48),
27133       holds_at(pos(Pos_Param52, Pos_Ret53), Time48).
27134 */
27135axiom(equals(Equals_Param49, Pos_Param52),
27136   
27137    [ not(equals(Equals_Param50, Dif_Param51)),
27138      { dif(Dif_Param51, Pos_Param52)
27139      },
27140      large(Dif_Param51),
27141      large(Pos_Param52),
27142      holds_at(pos(Dif_Param51, Pos_Ret53), Time48),
27143      holds_at(pos(Pos_Param52, Pos_Ret53), Time48)
27144    ]).
27145axiom(equals(Equals_Param49, Pos_Param52),
27146   
27147    [ not(holds_at(mounted(Equals_Param50, Pos_Param52),
27148                   Time48)),
27149      { dif(Dif_Param51, Pos_Param52)
27150      },
27151      large(Dif_Param51),
27152      large(Pos_Param52),
27153      holds_at(pos(Dif_Param51, Pos_Ret53), Time48),
27154      holds_at(pos(Pos_Param52, Pos_Ret53), Time48)
27155    ]).
27156
27157 /*  holds_at(mounted(Mounted_Param55, Dif_Param57), Time54) :-
27158       (   not(equals(Equals_Param56, Dif_Param57))
27159       ;   not(holds_at(mounted(Equals_Param56, Pos_Param58),
27160                        Time54))
27161       ),
27162       { dif(Dif_Param57, Pos_Param58)
27163       },
27164       large(Dif_Param57),
27165       large(Pos_Param58),
27166       holds_at(pos(Dif_Param57, Pos_Ret59), Time54),
27167       holds_at(pos(Pos_Param58, Pos_Ret59), Time54).
27168 */
27169axiom(holds_at(mounted(Mounted_Param55, Dif_Param57), Time54),
27170   
27171    [ not(equals(Equals_Param56, Dif_Param57)),
27172      dif(Dif_Param57, Pos_Param58),
27173      large(Dif_Param57),
27174      large(Pos_Param58),
27175      holds_at(pos(Dif_Param57, Pos_Ret59), Time54),
27176      holds_at(pos(Pos_Param58, Pos_Ret59), Time54)
27177    ]).
27178axiom(holds_at(mounted(Mounted_Param55, Dif_Param57), Time54),
27179   
27180    [ not(holds_at(mounted(Equals_Param56, Pos_Param58),
27181                   Time54)),
27182      dif(Dif_Param57, Pos_Param58),
27183      large(Dif_Param57),
27184      large(Pos_Param58),
27185      holds_at(pos(Dif_Param57, Pos_Ret59), Time54),
27186      holds_at(pos(Pos_Param58, Pos_Ret59), Time54)
27187    ]).
27188
27189
27190% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8437
27191% [human,position1,position2,time]
27192% HoldsAt(PosDeterminingFluent(human,position1),time) &
27193% HoldsAt(PosDeterminingFluent(human,position2),time) ->
27194% position1=position2.
27195% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8440
27196axiom(Position1=Position2,
27197   
27198    [ holds_at(posDeterminingFluent(Human, Position1), Time),
27199      holds_at(posDeterminingFluent(Human, Position2), Time)
27200    ]).
27201
27202
27203% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8442
27204% [animal,position,time]
27205% Initiates(Move(animal,position),Pos(animal,position),time).
27206% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8443
27207axiom(initiates(move(Animal, Position), pos(Animal, Position), Time),
27208    []).
27209
27210
27211% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8445
27212% [animal,position1,position2,time]
27213% HoldsAt(Pos(animal,position1),time) ->
27214% Terminates(Move(animal,position2),Pos(animal,position1),time).
27215% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8447
27216axiom(terminates(move(Animal, Position2), pos(Animal, Position1), Time),
27217    [holds_at(pos(Animal, Position1), Time)]).
27218
27219
27220% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8449
27221% [animal,position,time]
27222% Happens(Move(animal,position),time) ->
27223% !HoldsAt(Pos(animal,position),time).
27224% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8451
27225axiom(requires(move(Animal, Position), Time),
27226    [not(holds_at(pos(Animal, Position), Time))]).
27227
27228
27229% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8453
27230% [human,position,time]
27231% Happens(Move(human,position),time) ->
27232% !{animal} HoldsAt(Mounted(human,animal),time).
27233% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8455
27234axiom(requires(move(Human, Position), Time),
27235    [not(holds_at(mounted(Human, Animal), Time))]).
27236
27237
27238% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8457
27239% [human,gate,time]
27240% Initiates(Open(human,gate),Opened(gate),time).
27241% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8458
27242axiom(initiates(open(Human, Gate), opened(Gate), Time),
27243    []).
27244
27245
27246% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8460
27247% [human,gate,time]
27248% Happens(Open(human,gate),time) ->
27249% !HoldsAt(Opened(gate),time) &
27250% (!{animal} HoldsAt(Mounted(human,animal),time)) &
27251% ({position}
27252%  (Side1(gate)=position | Side2(gate)=position) &
27253%  HoldsAt(Pos(human,position),time)).
27254% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8466
27255axiom(requires(open(Human, Gate), Time),
27256   
27257    [ equals(side1(Gate), Position),
27258      not(holds_at(opened(Gate), Time)),
27259      not(holds_at(mounted(Human, Animal), Time)),
27260      holds_at(pos(Human, Position), Time)
27261    ]).
27262axiom(requires(open(Human, Gate), Time),
27263   
27264    [ equals(side2(Gate), Position),
27265      not(holds_at(opened(Gate), Time)),
27266      not(holds_at(mounted(Human, Animal), Time)),
27267      holds_at(pos(Human, Position), Time)
27268    ]).
27269
27270
27271% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8468
27272% [human,gate,time]
27273% Terminates(Close(human,gate),Opened(gate),time).
27274% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8469
27275axiom(terminates(close(Human, Gate), opened(Gate), Time),
27276    []).
27277
27278
27279% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8471
27280% [human,gate,time]
27281% Happens(Close(human,gate),time) ->
27282% HoldsAt(Opened(gate),time) &
27283% (!{animal} HoldsAt(Mounted(human,animal),time)) &
27284% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8475
27285% {position}% 
27286% (Side1(gate)=position | Side2(gate)=position) &
27287% HoldsAt(Pos(human,position),time).
27288
27289 /*   exists([Position],
27290             if(happens(close(Human, Gate), Time),
27291                 (holds_at(opened(Gate), Time), not(exists([Animal], holds_at(mounted(Human, Animal), Time))), (side1(Gate)=Position;side2(Gate)=Position), holds_at(pos(Human, Position), Time)))).
27292 */
27293
27294 /*  not(some(Some_Param, '$kolem_Fn_400'(Fn_400_Param, Close_Ret, Maptime, Fn_400_Ret))) :-
27295       happens(close(Fn_400_Param, Close_Ret), Maptime),
27296       (   not(holds_at(opened(Close_Ret), Maptime))
27297       ;   holds_at(mounted(Fn_400_Param, Fn_400_Ret), Maptime)
27298       ;   not(equals(side1(Close_Ret), Some_Param)),
27299           not(equals(side2(Close_Ret), Some_Param))
27300       ;   not(holds_at(pos(Fn_400_Param, Some_Param), Maptime))
27301       ).
27302 */
27303% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8477
27304axiom(not(some(Some_Param, '$kolem_Fn_400'(Fn_400_Param, Close_Ret, Maptime, Fn_400_Ret))),
27305   
27306    [ not(holds_at(opened(Close_Ret), Maptime)),
27307      happens(close(Fn_400_Param, Close_Ret), Maptime)
27308    ]).
27309axiom(not(some(Some_Param, '$kolem_Fn_400'(Fn_400_Param, Close_Ret, Maptime, Fn_400_Ret))),
27310   
27311    [ holds_at(mounted(Fn_400_Param, Fn_400_Ret), Maptime),
27312      happens(close(Fn_400_Param, Close_Ret), Maptime)
27313    ]).
27314axiom(not(some(Some_Param, '$kolem_Fn_400'(Fn_400_Param, Close_Ret, Maptime, Fn_400_Ret))),
27315   
27316    [ not(equals(side1(Close_Ret), Some_Param)),
27317      not(equals(side2(Close_Ret), Some_Param)),
27318      happens(close(Fn_400_Param, Close_Ret), Maptime)
27319    ]).
27320axiom(not(some(Some_Param, '$kolem_Fn_400'(Fn_400_Param, Close_Ret, Maptime, Fn_400_Ret))),
27321   
27322    [ not(holds_at(pos(Fn_400_Param, Some_Param), Maptime)),
27323      happens(close(Fn_400_Param, Close_Ret), Maptime)
27324    ]).
27325
27326 /*  not(happens(close(Close_Param, Close_Ret14), Maptime11)) :-
27327       (   not(holds_at(opened(Close_Ret14), Maptime11))
27328       ;   holds_at(mounted(Close_Param, Mounted_Ret), Maptime11)
27329       ;   not(equals(side1(Close_Ret14), Some_Param13)),
27330           not(equals(side2(Close_Ret14), Some_Param13))
27331       ;   not(holds_at(pos(Close_Param, Some_Param13),
27332                        Maptime11))
27333       ),
27334       some(Some_Param13,
27335            '$kolem_Fn_400'(Close_Param,
27336                            Close_Ret14,
27337                            Maptime11,
27338                            Mounted_Ret)).
27339 */
27340axiom(not(happens(close(Close_Param, Close_Ret14), Maptime11)),
27341   
27342    [ not(holds_at(opened(Close_Ret14), Maptime11)),
27343      some(Some_Param13,
27344           '$kolem_Fn_400'(Close_Param,
27345                           Close_Ret14,
27346                           Maptime11,
27347                           Mounted_Ret))
27348    ]).
27349axiom(not(happens(close(Close_Param, Close_Ret14), Maptime11)),
27350   
27351    [ holds_at(mounted(Close_Param, Mounted_Ret), Maptime11),
27352      some(Some_Param13,
27353           '$kolem_Fn_400'(Close_Param,
27354                           Close_Ret14,
27355                           Maptime11,
27356                           Mounted_Ret))
27357    ]).
27358axiom(not(happens(close(Close_Param, Close_Ret14), Maptime11)),
27359   
27360    [ not(equals(side1(Close_Ret14), Some_Param13)),
27361      not(equals(side2(Close_Ret14), Some_Param13)),
27362      some(Some_Param13,
27363           '$kolem_Fn_400'(Close_Param,
27364                           Close_Ret14,
27365                           Maptime11,
27366                           Mounted_Ret))
27367    ]).
27368axiom(not(happens(close(Close_Param, Close_Ret14), Maptime11)),
27369   
27370    [ not(holds_at(pos(Close_Param, Some_Param13), Maptime11)),
27371      some(Some_Param13,
27372           '$kolem_Fn_400'(Close_Param,
27373                           Close_Ret14,
27374                           Maptime11,
27375                           Mounted_Ret))
27376    ]).
27377
27378 /*  holds_at(opened(Opened_Ret), Time16) :-
27379       happens(close(Close_Param17, Opened_Ret), Time16),
27380       some(Some_Param18,
27381            '$kolem_Fn_400'(Close_Param17,
27382                            Opened_Ret,
27383                            Time16,
27384                            Fn_400_Ret20)).
27385 */
27386axiom(holds_at(opened(Opened_Ret), Time16),
27387   
27388    [ happens(close(Close_Param17, Opened_Ret), Time16),
27389      some(Some_Param18,
27390           '$kolem_Fn_400'(Close_Param17,
27391                           Opened_Ret,
27392                           Time16,
27393                           Fn_400_Ret20))
27394    ]).
27395
27396 /*  not(holds_at(mounted(Mounted_Param, Mounted_Ret24), Time21)) :-
27397       happens(close(Mounted_Param, Close_Ret25), Time21),
27398       some(Some_Param23,
27399            '$kolem_Fn_400'(Mounted_Param,
27400                            Close_Ret25,
27401                            Time21,
27402                            Mounted_Ret24)).
27403 */
27404axiom(not(holds_at(mounted(Mounted_Param, Mounted_Ret24), Time21)),
27405   
27406    [ happens(close(Mounted_Param, Close_Ret25), Time21),
27407      some(Some_Param23,
27408           '$kolem_Fn_400'(Mounted_Param,
27409                           Close_Ret25,
27410                           Time21,
27411                           Mounted_Ret24))
27412    ]).
27413
27414 /*  equals(side1(Side1_Ret), Some_Param28) :-
27415       not(equals(side2(Side1_Ret), Some_Param28)),
27416       happens(close(Close_Param27, Side1_Ret), Maptime26),
27417       some(Some_Param28,
27418            '$kolem_Fn_400'(Close_Param27,
27419                            Side1_Ret,
27420                            Maptime26,
27421                            Fn_400_Ret30)).
27422 */
27423axiom(equals(side1(Side1_Ret), Some_Param28),
27424   
27425    [ not(equals(side2(Side1_Ret), Some_Param28)),
27426      happens(close(Close_Param27, Side1_Ret), Maptime26),
27427      some(Some_Param28,
27428           '$kolem_Fn_400'(Close_Param27,
27429                           Side1_Ret,
27430                           Maptime26,
27431                           Fn_400_Ret30))
27432    ]).
27433
27434 /*  equals(side2(Side2_Ret), Some_Param33) :-
27435       not(equals(side1(Side2_Ret), Some_Param33)),
27436       happens(close(Close_Param32, Side2_Ret), Maptime31),
27437       some(Some_Param33,
27438            '$kolem_Fn_400'(Close_Param32,
27439                            Side2_Ret,
27440                            Maptime31,
27441                            Fn_400_Ret35)).
27442 */
27443axiom(equals(side2(Side2_Ret), Some_Param33),
27444   
27445    [ not(equals(side1(Side2_Ret), Some_Param33)),
27446      happens(close(Close_Param32, Side2_Ret), Maptime31),
27447      some(Some_Param33,
27448           '$kolem_Fn_400'(Close_Param32,
27449                           Side2_Ret,
27450                           Maptime31,
27451                           Fn_400_Ret35))
27452    ]).
27453
27454 /*  holds_at(pos(Pos_Param, Some_Param38), Time36) :-
27455       happens(close(Pos_Param, Close_Ret39), Time36),
27456       some(Some_Param38,
27457            '$kolem_Fn_400'(Pos_Param,
27458                            Close_Ret39,
27459                            Time36,
27460                            Fn_400_Ret40)).
27461 */
27462axiom(holds_at(pos(Pos_Param, Some_Param38), Time36),
27463   
27464    [ happens(close(Pos_Param, Close_Ret39), Time36),
27465      some(Some_Param38,
27466           '$kolem_Fn_400'(Pos_Param,
27467                           Close_Ret39,
27468                           Time36,
27469                           Fn_400_Ret40))
27470    ]).
27471
27472
27473% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8479
27474% [human,animal,position,time]
27475% HoldsAt(Mounted(human,animal),time) &
27476% HoldsAt(Pos(animal,position),time) ->
27477% HoldsAt(Pos(human,position),time).
27478% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8482
27479axiom(holds_at(pos(Human, Position), Time),
27480   
27481    [ holds_at(mounted(Human, Animal), Time),
27482      holds_at(pos(Animal, Position), Time)
27483    ]).
27484
27485
27486% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8484
27487% [animal,time]
27488% HoldsAt(Moves(animal),time) <->
27489% ({position}
27490%  HoldsAt(Pos(animal,position),time) &
27491%  !HoldsAt(Pos(animal,position),time+1)).
27492
27493 /*  holds_at(moves(Animal), Time) <->
27494       exists([Position],
27495               (holds_at(pos(Animal, Position), Time), not(holds_at(pos(Animal, Position), Time+1)))).
27496 */
27497% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8488
27498axiom(holds_at(moves(Animal), t),
27499   
27500    [ holds_at(pos(Animal, Position), t),
27501      not(holds_at(pos(Animal, Position), start)),
27502      b(t, start),
27503      ignore(t+1=start)
27504    ]).
27505
27506 /*   if(holds_at(moves(Animal), t),
27507         exists([Position],
27508                 (holds_at(pos(Animal, Position), t), not(holds_at(pos(Animal, Position), t+1))))).
27509 */
27510
27511 /*  not(holds_at(moves(Pos_Param), t)) :-
27512       (   not(holds_at(pos(Pos_Param, Pos_Ret), t))
27513       ;   holds_at(pos(Pos_Param, Pos_Ret), t+1)
27514       ).
27515 */
27516axiom(not(holds_at(moves(Pos_Param), t)),
27517    [not(holds_at(pos(Pos_Param, Pos_Ret), t))]).
27518axiom(not(holds_at(moves(Pos_Param), t)),
27519   
27520    [ holds_at(pos(Pos_Param, Pos_Ret), start),
27521      b(t, start),
27522      ignore(t+1=start)
27523    ]).
27524
27525 /*  holds_at(pos(Pos_Param5, Pos_Ret6), t) :-
27526       holds_at(moves(Pos_Param5), t).
27527 */
27528axiom(holds_at(pos(Pos_Param5, Pos_Ret6), t),
27529    [holds_at(moves(Pos_Param5), t)]).
27530
27531 /*  not(holds_at(pos(Pos_Param7, Pos_Ret8), t+1)) :-
27532       holds_at(moves(Pos_Param7), t).
27533 */
27534axiom(not(holds_at(pos(Pos_Param7, Pos_Ret8), start)),
27535    [holds_at(moves(Pos_Param7), t), b(t, start), ignore(t+1=start)]).
27536
27537
27538% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8490
27539% [human,time]
27540% HoldsAt(MountFails(human),time) <->
27541% ({animal}
27542%   Happens(Mount(human,animal),time) &
27543%   HoldsAt(Moves(animal),time)).
27544
27545 /*  holds_at(mountFails(Human), Time) <->
27546       exists([Animal],
27547               (happens(mount(Human, Animal), Time), holds_at(moves(Animal), Time))).
27548 */
27549% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8494
27550axiom(holds_at(mountFails(Human), Time),
27551   
27552    [ happens(mount(Human, Animal), Time),
27553      holds_at(moves(Animal), Time)
27554    ]).
27555
27556 /*   if(holds_at(mountFails(Human), Time),
27557         exists([Animal],
27558                 (happens(mount(Human, Animal), Time), holds_at(moves(Animal), Time)))).
27559 */
27560
27561 /*  not(holds_at(mountFails(Mount_Param), Time3)) :-
27562       (   not(happens(mount(Mount_Param, Mount_Ret), Time3))
27563       ;   not(holds_at(moves(Mount_Ret), Time3))
27564       ).
27565 */
27566axiom(not(holds_at(mountFails(Mount_Param), Time3)),
27567    [not(happens(mount(Mount_Param, Mount_Ret), Time3))]).
27568axiom(not(holds_at(mountFails(Mount_Param), Time3)),
27569    [not(holds_at(moves(Mount_Ret), Time3))]).
27570
27571 /*  happens(mount(Mount_Param7, Mount_Ret8), Maptime) :-
27572       holds_at(mountFails(Mount_Param7), Maptime).
27573 */
27574axiom(happens(mount(Mount_Param7, Mount_Ret8), Maptime),
27575    [holds_at(mountFails(Mount_Param7), Maptime)]).
27576
27577 /*  holds_at(moves(Moves_Ret), Time9) :-
27578       holds_at(mountFails(MountFails_Ret), Time9).
27579 */
27580axiom(holds_at(moves(Moves_Ret), Time9),
27581    [holds_at(mountFails(MountFails_Ret), Time9)]).
27582
27583
27584% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8496
27585% [human,animal,position,time]
27586% !HoldsAt(Moves(animal),time) ->
27587% Releases(Mount(human,animal),Pos(human,position),time).
27588% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8498
27589axiom(releases(mount(Human, Animal), pos(Human, Position), Time),
27590    [not(holds_at(moves(Animal), Time))]).
27591
27592
27593% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8500
27594% [human,animal,time]
27595% !HoldsAt(Moves(animal),time) ->
27596% Initiates(Mount(human,animal),Mounted(human,animal),time).
27597% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8502
27598axiom(initiates(mount(Human, Animal), mounted(Human, Animal), Time),
27599    [not(holds_at(moves(Animal), Time))]).
27600
27601
27602% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8504
27603% [human,animal,position,time]
27604% HoldsAt(Pos(animal,position),time) &
27605% HoldsAt(Moves(animal),time) ->
27606% Initiates(Mount(human,animal),Pos(human,position),time).
27607% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8507
27608axiom(initiates(mount(Human, Animal), pos(Human, Position), Time),
27609   
27610    [ holds_at(pos(Animal, Position), Time),
27611      holds_at(moves(Animal), Time)
27612    ]).
27613
27614
27615% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8509
27616% [human,animal,position,time]
27617% HoldsAt(Pos(human,position),time) &
27618% HoldsAt(Moves(animal),time) ->
27619% Terminates(Mount(human,animal),Pos(human,position),time).
27620% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8512
27621axiom(terminates(mount(Human, Animal), pos(Human, Position), Time),
27622   
27623    [ holds_at(pos(Human, Position), Time),
27624      holds_at(moves(Animal), Time)
27625    ]).
27626
27627
27628% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8514
27629% [human,animal,time]
27630% Happens(Mount(human,animal),time) ->
27631% Large(animal).
27632% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8516
27633axiom(requires(mount(Human, Animal), Time),
27634    [large(Animal)]).
27635
27636
27637% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8518
27638% [human,animal,time]
27639% HoldsAt(Mounted(human,animal),time) ->
27640% Large(animal).
27641% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8520
27642axiom(large(Animal),
27643    [holds_at(mounted(Human, Animal), Time)]).
27644
27645
27646% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8522
27647% [human1,human2,time]
27648% Happens(Mount(human1,human2),time) ->
27649% !Large(human1).
27650% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8524
27651axiom(requires(mount(Human1, Human2), Time),
27652    [not(large(Human1))]).
27653
27654
27655% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8526
27656% [human1,human2,time]
27657% HoldsAt(Mounted(human1,human2),time) ->
27658% !Large(human1).
27659% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8528
27660axiom(not(large(Human1)),
27661    [holds_at(mounted(Human1, Human2), Time)]).
27662
27663
27664% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8530
27665% [human,animal,time]
27666% Happens(Mount(human,animal),time) ->
27667% !{human1} human1!=human & HoldsAt(Mounted(human1,animal),time).
27668% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8532
27669axiom(requires(mount(Human, Animal), Time),
27670    [not({dif(Human1, Human)})]).
27671axiom(requires(mount(Human, Animal), Time),
27672    [not(holds_at(mounted(Human1, Animal), Time))]).
27673
27674
27675% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8534
27676% [human1,human2,animal,time]
27677% HoldsAt(Mounted(human1,animal),time) &
27678% HoldsAt(Mounted(human2,animal),time) ->
27679% human1=human2.
27680% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8537
27681axiom(Human1=Human2,
27682   
27683    [ holds_at(mounted(Human1, Animal), Time),
27684      holds_at(mounted(Human2, Animal), Time)
27685    ]).
27686
27687
27688% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8539
27689% [human,animal,time]
27690% Happens(Mount(human,animal),time) ->
27691% !{human1} human1!=human & HoldsAt(Mounted(human1,human),time).
27692% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8541
27693axiom(requires(mount(Human, Animal), Time),
27694    [not({dif(Human1, Human)})]).
27695axiom(requires(mount(Human, Animal), Time),
27696    [not(holds_at(mounted(Human1, Human), Time))]).
27697
27698
27699% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8543
27700% [human1,human2,time]
27701% Happens(Mount(human1,human2),time) ->
27702% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8545
27703% {animal}%  HoldsAt(Mounted(human2,animal),time).
27704
27705 /*  exists([Animal],
27706          if(happens(mount(Human1,Human2),Time),
27707   	  holds_at(mounted(Human2,Animal),Time))).
27708 */
27709
27710 /*  holds_at(mounted(Mounted_Param, Some_Param), Time5) :-
27711       happens(mount(Mount_Param, Mounted_Param), Time5),
27712       some(Some_Param,
27713            '$kolem_Fn_408'(Mount_Param, Mounted_Param, Time5)).
27714 */
27715axiom(holds_at(mounted(Mounted_Param, Some_Param), Time5),
27716   
27717    [ happens(mount(Mount_Param, Mounted_Param), Time5),
27718      some(Some_Param,
27719           '$kolem_Fn_408'(Mount_Param, Mounted_Param, Time5))
27720    ]).
27721
27722 /*  not(happens(mount(Mount_Param10, Mounted_Param11), Maptime)) :-
27723       not(holds_at(mounted(Mounted_Param11, Some_Param12),
27724                    Maptime)),
27725       some(Some_Param12,
27726            '$kolem_Fn_408'(Mount_Param10,
27727                            Mounted_Param11,
27728                            Maptime)).
27729 */
27730axiom(not(happens(mount(Mount_Param10, Mounted_Param11), Maptime)),
27731   
27732    [ not(holds_at(mounted(Mounted_Param11, Some_Param12),
27733                   Maptime)),
27734      some(Some_Param12,
27735           '$kolem_Fn_408'(Mount_Param10,
27736                           Mounted_Param11,
27737                           Maptime))
27738    ]).
27739
27740 /*  not(some(Some_Param14, '$kolem_Fn_408'(Fn_408_Param, Mounted_Param16, Time13))) :-
27741       not(holds_at(mounted(Mounted_Param16, Some_Param14),
27742                    Time13)),
27743       happens(mount(Fn_408_Param, Mounted_Param16), Time13).
27744 */
27745axiom(not(some(Some_Param14, '$kolem_Fn_408'(Fn_408_Param, Mounted_Param16, Time13))),
27746   
27747    [ not(holds_at(mounted(Mounted_Param16, Some_Param14),
27748                   Time13)),
27749      happens(mount(Fn_408_Param, Mounted_Param16), Time13)
27750    ]).
27751
27752
27753% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8547
27754% [human1,human2,time]
27755% HoldsAt(Mounted(human1,human2),time) ->
27756% !{animal} HoldsAt(Mounted(human2,animal),time).
27757% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8549
27758axiom(not(exists([Animal], holds_at(mounted(Human2, Animal), Time))),
27759    [holds_at(mounted(Human1, Human2), Time)]).
27760
27761
27762% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8551
27763% [human,animal,time]
27764% Happens(Mount(human,animal),time) ->
27765% !{animal1} HoldsAt(Mounted(human,animal1),time).
27766% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8553
27767axiom(requires(mount(Human, Animal), Time),
27768    [not(holds_at(mounted(Human, Animal1), Time))]).
27769
27770
27771% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8555
27772% [human,animal,time]
27773% !HoldsAt(Moves(animal),time) ->
27774% Terminates(GetOff(human,animal),Mounted(human,animal),time).
27775% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8557
27776axiom(terminates(getOff(Human, Animal), mounted(Human, Animal), Time),
27777    [not(holds_at(moves(Animal), Time))]).
27778
27779
27780% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8559
27781% [human,animal,position,time]
27782% !HoldsAt(Moves(animal),time) &
27783% HoldsAt(PosDeterminingFluent(human,position),time) ->
27784% Initiates(GetOff(human,animal),Pos(human,position),time).
27785% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8562
27786axiom(initiates(getOff(Human, Animal), pos(Human, Position), Time),
27787   
27788    [ not(holds_at(moves(Animal), Time)),
27789      holds_at(posDeterminingFluent(Human, Position), Time)
27790    ]).
27791
27792
27793% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8564
27794% [human,animal,position,time]
27795% !HoldsAt(Moves(animal),time) &
27796% HoldsAt(Pos(human,position),time) ->
27797% Terminates(GetOff(human,animal),Pos(human,position),time).
27798% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8567
27799axiom(terminates(getOff(Human, Animal), pos(Human, Position), Time),
27800   
27801    [ not(holds_at(moves(Animal), Time)),
27802      holds_at(pos(Human, Position), Time)
27803    ]).
27804
27805
27806% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8569
27807% [human,animal,position1,position2,time]
27808% !HoldsAt(Moves(animal),time) &
27809% HoldsAt(Pos(human,position1),time) &
27810% position1!=position2 ->
27811% Terminates(GetOff(human,animal),Pos(human,position2),time).
27812% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8573
27813axiom(terminates(getOff(Human, Animal), pos(Human, Position2), Time),
27814   
27815    [ not(holds_at(moves(Animal), Time)),
27816      holds_at(pos(Human, Position1), Time),
27817      { dif(Position1, Position2)
27818      }
27819    ]).
27820
27821
27822% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8575
27823% [human,animal,time]
27824% Happens(GetOff(human,animal),time) ->
27825% HoldsAt(Mounted(human,animal),time).
27826% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8577
27827axiom(requires(getOff(Human, Animal), Time),
27828    [holds_at(mounted(Human, Animal), Time)]).
27829
27830
27831% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8579
27832% [animal1,human,time]
27833% HoldsAt(ThrowOffFails(animal1,human),time) <->
27834% ({position,animal2}
27835%  animal2!=human &
27836%  HoldsAt(PosDeterminingFluent(human,position),time) &
27837%  Large(animal2) &
27838%  HoldsAt(Pos(animal2,position),time+1)).
27839
27840 /*  holds_at(throwOffFails(Animal1, Human), Time) <->
27841       exists([Position, Animal2],
27842               (Animal2\=Human, holds_at(posDeterminingFluent(Human, Position), Time), large(Animal2), holds_at(pos(Animal2, Position), Time+1))).
27843 */
27844% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8585
27845axiom(holds_at(throwOffFails(Animal1, Human), t),
27846   
27847    [ dif(Animal2, Human),
27848      holds_at(posDeterminingFluent(Human, Position), t),
27849      large(Animal2),
27850      holds_at(pos(Animal2, Position), start),
27851      b(t, start),
27852      ignore(t+1=start)
27853    ]).
27854
27855 /*   if(holds_at(throwOffFails(Animal1, Human), t),
27856         exists([Position, Animal2],
27857                 (Animal2\=Human, holds_at(posDeterminingFluent(Human, Position), t), large(Animal2), holds_at(pos(Animal2, Position), t+1)))).
27858 */
27859
27860 /*  not(holds_at(throwOffFails(ThrowOffFails_Param, PosDeterminingFluent_Param), t)) :-
27861       (   not({dif(Dif_Param, PosDeterminingFluent_Param)})
27862       ;   not(holds_at(posDeterminingFluent(PosDeterminingFluent_Param,
27863                                             PosDeterminingFluent_Ret),
27864                        t))
27865       ;   not(large(Dif_Param))
27866       ;   not(holds_at(pos(Dif_Param, PosDeterminingFluent_Ret), t+1))
27867       ).
27868 */
27869axiom(not(holds_at(throwOffFails(ThrowOffFails_Param, PosDeterminingFluent_Param), t)),
27870    [not({dif(Dif_Param, PosDeterminingFluent_Param)})]).
27871axiom(not(holds_at(throwOffFails(ThrowOffFails_Param, PosDeterminingFluent_Param), t)),
27872   
27873    [ not(holds_at(posDeterminingFluent(PosDeterminingFluent_Param,
27874                                        PosDeterminingFluent_Ret),
27875                   t))
27876    ]).
27877axiom(not(holds_at(throwOffFails(ThrowOffFails_Param, PosDeterminingFluent_Param), t)),
27878    [not(large(Dif_Param))]).
27879axiom(not(holds_at(throwOffFails(ThrowOffFails_Param, PosDeterminingFluent_Param), t)),
27880   
27881    [ not(holds_at(pos(Dif_Param, PosDeterminingFluent_Ret), start)),
27882      b(t, start),
27883      ignore(t+1=start)
27884    ]).
27885
27886 /*  { dif(Dif_Param9, Dif_Ret)
27887   } :-
27888       holds_at(throwOffFails(ThrowOffFails_Param10, Dif_Ret), t).
27889 */
27890axiom({ dif(Dif_Param9, Dif_Ret)
27891},
27892    [holds_at(throwOffFails(ThrowOffFails_Param10, Dif_Ret), t)]).
27893
27894 /*  holds_at(posDeterminingFluent(PosDeterminingFluent_Param12, PosDeterminingFluent_Ret14), t) :-
27895       holds_at(throwOffFails(ThrowOffFails_Param13,
27896                              PosDeterminingFluent_Param12),
27897                t).
27898 */
27899axiom(holds_at(posDeterminingFluent(PosDeterminingFluent_Param12, PosDeterminingFluent_Ret14), t),
27900   
27901    [ holds_at(throwOffFails(ThrowOffFails_Param13,
27902                             PosDeterminingFluent_Param12),
27903               t)
27904    ]).
27905
27906 /*  large(Large_Ret) :-
27907       holds_at(throwOffFails(ThrowOffFails_Param15,
27908                              ThrowOffFails_Ret),
27909                t).
27910 */
27911axiom(large(Large_Ret),
27912   
27913    [ holds_at(throwOffFails(ThrowOffFails_Param15,
27914                             ThrowOffFails_Ret),
27915               t)
27916    ]).
27917
27918 /*  holds_at(pos(Pos_Param, Pos_Ret), t+1) :-
27919       holds_at(throwOffFails(ThrowOffFails_Param19,
27920                              ThrowOffFails_Ret21),
27921                t).
27922 */
27923axiom(holds_at(pos(Pos_Param, Pos_Ret), start),
27924   
27925    [ holds_at(throwOffFails(ThrowOffFails_Param19,
27926                             ThrowOffFails_Ret21),
27927               t),
27928      b(t, start),
27929      ignore(t+1=start)
27930    ]).
27931
27932
27933% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8587
27934% [animal,human,position,time]
27935% HoldsAt(PosDeterminingFluent(human,position),time) &
27936% !HoldsAt(ThrowOffFails(animal,human),time) ->
27937% Initiates(ThrowOff(animal,human),Pos(human,position),time).
27938% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8590
27939axiom(initiates(throwOff(Animal, Human), pos(Human, Position), Time),
27940   
27941    [ holds_at(posDeterminingFluent(Human, Position), Time),
27942      not(holds_at(throwOffFails(Animal, Human), Time))
27943    ]).
27944
27945
27946% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8592
27947% [animal,human,position,time]
27948% HoldsAt(Pos(human,position),time) &
27949% !HoldsAt(ThrowOffFails(animal,human),time) ->
27950% Terminates(ThrowOff(animal,human),Pos(human,position),time).
27951% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8595
27952axiom(terminates(throwOff(Animal, Human), pos(Human, Position), Time),
27953   
27954    [ holds_at(pos(Human, Position), Time),
27955      not(holds_at(throwOffFails(Animal, Human), Time))
27956    ]).
27957
27958
27959% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8597
27960% [animal,human,position1,position2,time]
27961% !HoldsAt(ThrowOffFails(animal,human),time) &
27962% HoldsAt(Pos(human,position1),time) &
27963% !HoldsAt(PosDeterminingFluent(human,position2),time) &
27964% position1!=position2 ->
27965% Terminates(ThrowOff(animal,human),Pos(human,position2),time).
27966% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8602
27967axiom(terminates(throwOff(Animal, Human), pos(Human, Position2), Time),
27968   
27969    [ not(holds_at(throwOffFails(Animal, Human), Time)),
27970      holds_at(pos(Human, Position1), Time),
27971      not(holds_at(posDeterminingFluent(Human, Position2),
27972                   Time)),
27973      { dif(Position1, Position2)
27974      }
27975    ]).
27976
27977
27978% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8604
27979% [human,time]
27980% (!{animal} Happens(ThrowOff(animal,human),time) |
27981%            Happens(GetOff(human,animal),time)) ->
27982% HoldsAt(PosDeterminingFluent(human,1),time).
27983% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8607
27984axiom(holds_at(posDeterminingFluent(Human, 1), Time),
27985   
27986    [ not(happens(throwOff(Animal, Human), Time)),
27987      not(happens(getOff(Human, Animal), Time))
27988    ]).
27989
27990
27991% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8609
27992% [human,position,animal1,animal2,time]
27993% HoldsAt(PosDeterminingFluent(human,position),time) &
27994% HoldsAt(ThrowOffFails(animal1,human),time) &
27995% HoldsAt(Pos(animal2,position),time) ->
27996% Initiates(ThrowOff(animal1,human),Mounted(human,animal2),time).
27997% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8613
27998axiom(initiates(throwOff(Animal1, Human), mounted(Human, Animal2), Time),
27999   
28000    [ holds_at(posDeterminingFluent(Human, Position), Time),
28001      holds_at(throwOffFails(Animal1, Human), Time),
28002      holds_at(pos(Animal2, Position), Time)
28003    ]).
28004
28005
28006% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8615
28007% [human,animal,time]
28008% !HoldsAt(ThrowOffFails(animal,human),time) ->
28009% Terminates(ThrowOff(animal,human),Mounted(human,animal),time).
28010% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8617
28011axiom(terminates(throwOff(Animal, Human), mounted(Human, Animal), Time),
28012    [not(holds_at(throwOffFails(Animal, Human), Time))]).
28013
28014
28015% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8619
28016% [animal,human,time]
28017% Happens(ThrowOff(animal,human),time) ->
28018% HoldsAt(Mounted(human,animal),time).
28019% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8621
28020axiom(requires(throwOff(Animal, Human), Time),
28021    [holds_at(mounted(Human, Animal), Time)]).
28022
28023
28024% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8623
28025% [animal,human,time]
28026% Happens(ThrowOff(animal,human),time) ->
28027% !Happens(GetOff(human,animal),time).
28028% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8625
28029axiom(not(happens(getOff(Human, Animal), Time)),
28030    [happens(throwOff(Animal, Human), Time)]).
28031
28032
28033% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8627
28034% [animal,human,time]
28035% Happens(GetOff(human,animal),time) ->
28036% !Happens(ThrowOff(animal,human),time).
28037% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8629
28038axiom(not(happens(throwOff(Animal, Human), Time)),
28039    [happens(getOff(Human, Animal), Time)]).
28040
28041
28042% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8631
28043% [position1,position2,time]
28044% Accessible(position1,position2,time) <->
28045% (Neighbor(position1,position2) &
28046%  !{gate} Sides(position1,position2,gate) &
28047%          !HoldsAt(Opened(gate),time)).
28048
28049 /*  accessible(Position1, Position2, Time) <->
28050       thereExists((neighbor(Position1, Position2), not([gate])),
28051                    (sides(Position1, Position2, gate), not(holds_at(opened(gate), Time)))).
28052 */
28053% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8635
28054axiom(accessible(Position1, Position2, Time),
28055   
28056    [ thereExists((neighbor(Position1, Position2), not([gate])),
28057                   (sides(Position1, Position2, gate), not(holds_at(opened(gate), Time))))
28058    ]).
28059axiom(thereExists((neighbor(Position1, Position2), not([gate])),  (sides(Position1, Position2, gate), not(holds_at(opened(gate), Time)))),
28060    [accessible(Position1, Position2, Time)]).
28061
28062
28063% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8637
28064% [animal,position1,position2,time]
28065% (position1!=position2 &
28066%  HoldsAt(Pos(animal,position1),time) &
28067%  HoldsAt(Pos(animal,position2),time+1)) ->
28068% Accessible(position1,position2,time).
28069% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8641
28070axiom(accessible(Position1, Position2, t),
28071   
28072    [ { dif(Position1, Position2)
28073      },
28074      holds_at(pos(Animal, Position1), t),
28075      holds_at(pos(Animal, Position2), start),
28076      b(t, start),
28077      ignore(t+1=start)
28078    ]).
28079
28080
28081% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8643
28082% [human,time]
28083% HoldsAt(AbnormalEncroachment(human),time) <->
28084% (HoldsAt(MountFails(human),time) |
28085%  ({position,animal1,animal2}
28086%    HoldsAt(PosDeterminingFluent(human,position),time) &
28087%    !HoldsAt(ThrowOffFails(animal2,human),time) &
28088%    Happens(ThrowOff(animal2,human),time) &
28089%    animal1!=human &
28090%    Large(animal1) &
28091%    HoldsAt(Pos(animal1,position),time) &
28092%    !HoldsAt(Pos(animal1,position),time+1))).
28093
28094 /*  holds_at(abnormalEncroachment(Human), Time) <->
28095       (   holds_at(mountFails(Human), Time)
28096       ;   exists([Position, Animal1, Animal2],
28097                   (holds_at(posDeterminingFluent(Human, Position), Time), not(holds_at(throwOffFails(Animal2, Human), Time)), happens(throwOff(Animal2, Human), Time), Animal1\=Human, large(Animal1), holds_at(pos(Animal1, Position), Time), not(holds_at(pos(Animal1, Position), Time+1))))
28098       ).
28099 */
28100% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8653
28101axiom(holds_at(abnormalEncroachment(Human), Time),
28102    [holds_at(mountFails(Human), Time)]).
28103axiom(holds_at(abnormalEncroachment(Human), t),
28104   
28105    [ holds_at(posDeterminingFluent(Human, Position), t),
28106      not(holds_at(throwOffFails(Animal2, Human), t)),
28107      happens(throwOff(Animal2, Human), t),
28108      dif(Animal1, Human),
28109      large(Animal1),
28110      holds_at(pos(Animal1, Position), t),
28111      not(holds_at(pos(Animal1, Position), start)),
28112      b(t, start),
28113      ignore(t+1=start)
28114    ]).
28115
28116 /*   if(holds_at(abnormalEncroachment(Human), t),
28117          (holds_at(mountFails(Human), t);exists([Position, Animal1, Animal2],  (holds_at(posDeterminingFluent(Human, Position), t), not(holds_at(throwOffFails(Animal2, Human), t)), happens(throwOff(Animal2, Human), t), Animal1\=Human, large(Animal1), holds_at(pos(Animal1, Position), t), not(holds_at(pos(Animal1, Position), t+1)))))).
28118 */
28119
28120 /*  not(holds_at(abnormalEncroachment(PosDeterminingFluent_Param), t)) :-
28121       not(holds_at(mountFails(PosDeterminingFluent_Param), t)),
28122       (   not(holds_at(posDeterminingFluent(PosDeterminingFluent_Param,
28123                                             PosDeterminingFluent_Ret),
28124                        t))
28125       ;   holds_at(throwOffFails(ThrowOffFails_Param,
28126                                  PosDeterminingFluent_Param),
28127                    t)
28128       ;   not(happens(throwOff(ThrowOffFails_Param,
28129                                PosDeterminingFluent_Param),
28130                       t))
28131       ;   not({dif(Dif_Param, PosDeterminingFluent_Param)})
28132       ;   not(large(Dif_Param))
28133       ;   not(holds_at(pos(Dif_Param, PosDeterminingFluent_Ret), t))
28134       ;   holds_at(pos(Dif_Param, PosDeterminingFluent_Ret), t+1)
28135       ).
28136 */
28137axiom(not(holds_at(abnormalEncroachment(PosDeterminingFluent_Param), t)),
28138   
28139    [ not(holds_at(posDeterminingFluent(PosDeterminingFluent_Param,
28140                                        PosDeterminingFluent_Ret),
28141                   t)),
28142      not(holds_at(mountFails(PosDeterminingFluent_Param), t))
28143    ]).
28144axiom(not(holds_at(abnormalEncroachment(PosDeterminingFluent_Param), t)),
28145   
28146    [ holds_at(throwOffFails(ThrowOffFails_Param,
28147                             PosDeterminingFluent_Param),
28148               t),
28149      not(holds_at(mountFails(PosDeterminingFluent_Param), t))
28150    ]).
28151axiom(not(holds_at(abnormalEncroachment(PosDeterminingFluent_Param), t)),
28152   
28153    [ not(happens(throwOff(ThrowOffFails_Param,
28154                           PosDeterminingFluent_Param),
28155                  t)),
28156      not(holds_at(mountFails(PosDeterminingFluent_Param), t))
28157    ]).
28158axiom(not(holds_at(abnormalEncroachment(PosDeterminingFluent_Param), t)),
28159   
28160    [ not({dif(Dif_Param, PosDeterminingFluent_Param)}),
28161      not(holds_at(mountFails(PosDeterminingFluent_Param), t))
28162    ]).
28163axiom(not(holds_at(abnormalEncroachment(PosDeterminingFluent_Param), t)),
28164   
28165    [ not(large(Dif_Param)),
28166      not(holds_at(mountFails(PosDeterminingFluent_Param), t))
28167    ]).
28168axiom(not(holds_at(abnormalEncroachment(PosDeterminingFluent_Param), t)),
28169   
28170    [ not(holds_at(pos(Dif_Param, PosDeterminingFluent_Ret), t)),
28171      not(holds_at(mountFails(PosDeterminingFluent_Param), t))
28172    ]).
28173axiom(not(holds_at(abnormalEncroachment(PosDeterminingFluent_Param), t)),
28174   
28175    [ holds_at(pos(Dif_Param, PosDeterminingFluent_Ret), start),
28176      not(holds_at(mountFails(PosDeterminingFluent_Param), t)),
28177      b(t, start),
28178      ignore(t+1=start)
28179    ]).
28180
28181 /*  holds_at(mountFails(PosDeterminingFluent_Param9), t) :-
28182       (   not(holds_at(posDeterminingFluent(PosDeterminingFluent_Param9,
28183                                             PosDeterminingFluent_Ret12),
28184                        t))
28185       ;   holds_at(throwOffFails(ThrowOffFails_Param10,
28186                                  PosDeterminingFluent_Param9),
28187                    t)
28188       ;   not(happens(throwOff(ThrowOffFails_Param10,
28189                                PosDeterminingFluent_Param9),
28190                       t))
28191       ;   not({dif(Dif_Param11, PosDeterminingFluent_Param9)})
28192       ;   not(large(Dif_Param11))
28193       ;   not(holds_at(pos(Dif_Param11, PosDeterminingFluent_Ret12),
28194                        t))
28195       ;   holds_at(pos(Dif_Param11, PosDeterminingFluent_Ret12), t+1)
28196       ),
28197       holds_at(abnormalEncroachment(PosDeterminingFluent_Param9), t).
28198 */
28199axiom(holds_at(mountFails(PosDeterminingFluent_Param9), t),
28200   
28201    [ not(holds_at(posDeterminingFluent(PosDeterminingFluent_Param9,
28202                                        PosDeterminingFluent_Ret12),
28203                   t)),
28204      holds_at(abnormalEncroachment(PosDeterminingFluent_Param9), t)
28205    ]).
28206axiom(holds_at(mountFails(PosDeterminingFluent_Param9), t),
28207   
28208    [ holds_at(throwOffFails(ThrowOffFails_Param10,
28209                             PosDeterminingFluent_Param9),
28210               t),
28211      holds_at(abnormalEncroachment(PosDeterminingFluent_Param9), t)
28212    ]).
28213axiom(holds_at(mountFails(PosDeterminingFluent_Param9), t),
28214   
28215    [ not(happens(throwOff(ThrowOffFails_Param10,
28216                           PosDeterminingFluent_Param9),
28217                  t)),
28218      holds_at(abnormalEncroachment(PosDeterminingFluent_Param9), t)
28219    ]).
28220axiom(holds_at(mountFails(PosDeterminingFluent_Param9), t),
28221   
28222    [ not({dif(Dif_Param11, PosDeterminingFluent_Param9)}),
28223      holds_at(abnormalEncroachment(PosDeterminingFluent_Param9), t)
28224    ]).
28225axiom(holds_at(mountFails(PosDeterminingFluent_Param9), t),
28226   
28227    [ not(large(Dif_Param11)),
28228      holds_at(abnormalEncroachment(PosDeterminingFluent_Param9), t)
28229    ]).
28230axiom(holds_at(mountFails(PosDeterminingFluent_Param9), t),
28231   
28232    [ not(holds_at(pos(Dif_Param11, PosDeterminingFluent_Ret12), t)),
28233      holds_at(abnormalEncroachment(PosDeterminingFluent_Param9), t)
28234    ]).
28235axiom(holds_at(mountFails(PosDeterminingFluent_Param9), t),
28236   
28237    [ holds_at(pos(Dif_Param11, PosDeterminingFluent_Ret12), start),
28238      holds_at(abnormalEncroachment(PosDeterminingFluent_Param9), t),
28239      b(t, start),
28240      ignore(t+1=start)
28241    ]).
28242
28243 /*  holds_at(posDeterminingFluent(PosDeterminingFluent_Param13, PosDeterminingFluent_Ret14), t) :-
28244       not(holds_at(mountFails(PosDeterminingFluent_Param13), t)),
28245       holds_at(abnormalEncroachment(PosDeterminingFluent_Param13), t).
28246 */
28247axiom(holds_at(posDeterminingFluent(PosDeterminingFluent_Param13, PosDeterminingFluent_Ret14), t),
28248   
28249    [ not(holds_at(mountFails(PosDeterminingFluent_Param13), t)),
28250      holds_at(abnormalEncroachment(PosDeterminingFluent_Param13), t)
28251    ]).
28252
28253 /*  not(holds_at(throwOffFails(ThrowOffFails_Param15, ThrowOffFails_Ret), t)) :-
28254       not(holds_at(mountFails(ThrowOffFails_Ret), t)),
28255       holds_at(abnormalEncroachment(ThrowOffFails_Ret), t).
28256 */
28257axiom(not(holds_at(throwOffFails(ThrowOffFails_Param15, ThrowOffFails_Ret), t)),
28258   
28259    [ not(holds_at(mountFails(ThrowOffFails_Ret), t)),
28260      holds_at(abnormalEncroachment(ThrowOffFails_Ret), t)
28261    ]).
28262
28263 /*  happens(throwOff(ThrowOff_Param, ThrowOff_Ret), t) :-
28264       not(holds_at(mountFails(ThrowOff_Ret), t)),
28265       holds_at(abnormalEncroachment(ThrowOff_Ret), t).
28266 */
28267axiom(happens(throwOff(ThrowOff_Param, ThrowOff_Ret), t),
28268   
28269    [ not(holds_at(mountFails(ThrowOff_Ret), t)),
28270      holds_at(abnormalEncroachment(ThrowOff_Ret), t)
28271    ]).
28272
28273 /*  { dif(Dif_Param19, Dif_Ret)
28274   } :-
28275       not(holds_at(mountFails(Dif_Ret), t)),
28276       holds_at(abnormalEncroachment(Dif_Ret), t).
28277 */
28278axiom({ dif(Dif_Param19, Dif_Ret)
28279},
28280   
28281    [ not(holds_at(mountFails(Dif_Ret), t)),
28282      holds_at(abnormalEncroachment(Dif_Ret), t)
28283    ]).
28284
28285 /*  large(Large_Ret) :-
28286       not(holds_at(mountFails(MountFails_Ret), t)),
28287       holds_at(abnormalEncroachment(MountFails_Ret), t).
28288 */
28289axiom(large(Large_Ret),
28290   
28291    [ not(holds_at(mountFails(MountFails_Ret), t)),
28292      holds_at(abnormalEncroachment(MountFails_Ret), t)
28293    ]).
28294
28295 /*  holds_at(pos(Pos_Param, Pos_Ret), t) :-
28296       not(holds_at(mountFails(MountFails_Ret25), t)),
28297       holds_at(abnormalEncroachment(MountFails_Ret25), t).
28298 */
28299axiom(holds_at(pos(Pos_Param, Pos_Ret), t),
28300   
28301    [ not(holds_at(mountFails(MountFails_Ret25), t)),
28302      holds_at(abnormalEncroachment(MountFails_Ret25), t)
28303    ]).
28304
28305 /*  not(holds_at(pos(Pos_Param26, Pos_Ret27), t+1)) :-
28306       not(holds_at(mountFails(MountFails_Ret28), t)),
28307       holds_at(abnormalEncroachment(MountFails_Ret28), t).
28308 */
28309axiom(not(holds_at(pos(Pos_Param26, Pos_Ret27), start)),
28310   
28311    [ not(holds_at(mountFails(MountFails_Ret28), t)),
28312      holds_at(abnormalEncroachment(MountFails_Ret28), t),
28313      b(t, start),
28314      ignore(t+1=start)
28315    ]).
28316
28317
28318% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8655
28319% [animal1,animal2,position,time]
28320% HoldsAt(Pos(animal1,position),time) &
28321% !HoldsAt(Pos(animal1,position),time+1) &
28322% !HoldsAt(Pos(animal2,position),time) &
28323% HoldsAt(Pos(animal2,position),time+1) ->
28324% (!Large(animal1) |
28325%  !Large(animal2) |
28326%  ({human} human=animal2 & HoldsAt(AbnormalEncroachment(human),time))).
28327
28328 /*   if((holds_at(pos(Animal1, Position), Time), not(holds_at(pos(Animal1, Position), Time+1)), not(holds_at(pos(Animal2, Position), Time)), holds_at(pos(Animal2, Position), Time+1)),
28329          (not(large(Animal1));not(large(Animal2));exists([Human],  (Human=Animal2, holds_at(abnormalEncroachment(Human), Time))))).
28330 */
28331
28332 /*  not(holds_at(pos(Pos_Param, Pos_Ret), Time5)) :-
28333       ( not(holds_at(pos(Pos_Param, Pos_Ret), Time5+1)),
28334         not(holds_at(pos(Pos_Param7, Pos_Ret), Time5)),
28335         holds_at(pos(Pos_Param7, Pos_Ret), Time5+1)
28336       ),
28337       large(Pos_Param),
28338       large(Pos_Param7),
28339       (   not(equals(Equals_Param, Pos_Param7))
28340       ;   not(holds_at(abnormalEncroachment(Equals_Param), Time5))
28341       ).
28342 */
28343% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8662
28344axiom(not(holds_at(pos(Pos_Param, Pos_Ret), t)),
28345   
28346    [ not(equals(Equals_Param, Pos_Param7)),
28347      not(holds_at(pos(Pos_Param, Pos_Ret), start)),
28348      not(holds_at(pos(Pos_Param7, Pos_Ret), t)),
28349      holds_at(pos(Pos_Param7, Pos_Ret), start),
28350      large(Pos_Param),
28351      large(Pos_Param7),
28352      b(t, start),
28353      ignore(t+1=start)
28354    ]).
28355axiom(not(holds_at(pos(Pos_Param, Pos_Ret), t)),
28356   
28357    [ not(holds_at(abnormalEncroachment(Equals_Param), t)),
28358      not(holds_at(pos(Pos_Param, Pos_Ret), start)),
28359      not(holds_at(pos(Pos_Param7, Pos_Ret), t)),
28360      holds_at(pos(Pos_Param7, Pos_Ret), start),
28361      large(Pos_Param),
28362      large(Pos_Param7),
28363      b(t, start),
28364      ignore(t+1=start)
28365    ]).
28366
28367 /*  holds_at(pos(Pos_Param11, Pos_Ret14), Time10+1) :-
28368       ( not(holds_at(pos(Pos_Param12, Pos_Ret14), Time10)),
28369         holds_at(pos(Pos_Param12, Pos_Ret14), Time10+1)
28370       ),
28371       holds_at(pos(Pos_Param11, Pos_Ret14), Time10),
28372       large(Pos_Param11),
28373       large(Pos_Param12),
28374       (   not(equals(Equals_Param13, Pos_Param12))
28375       ;   not(holds_at(abnormalEncroachment(Equals_Param13), Time10))
28376       ).
28377 */
28378axiom(holds_at(pos(Pos_Param11, Pos_Ret14), start),
28379   
28380    [ not(equals(Equals_Param13, Pos_Param12)),
28381      not(holds_at(pos(Pos_Param12, Pos_Ret14), t)),
28382      holds_at(pos(Pos_Param12, Pos_Ret14), start),
28383      holds_at(pos(Pos_Param11, Pos_Ret14), t),
28384      large(Pos_Param11),
28385      large(Pos_Param12),
28386      b(t, start),
28387      ignore(t+1=start)
28388    ]).
28389axiom(holds_at(pos(Pos_Param11, Pos_Ret14), start),
28390   
28391    [ not(holds_at(abnormalEncroachment(Equals_Param13), t)),
28392      not(holds_at(pos(Pos_Param12, Pos_Ret14), t)),
28393      holds_at(pos(Pos_Param12, Pos_Ret14), start),
28394      holds_at(pos(Pos_Param11, Pos_Ret14), t),
28395      large(Pos_Param11),
28396      large(Pos_Param12),
28397      b(t, start),
28398      ignore(t+1=start)
28399    ]).
28400
28401 /*  holds_at(pos(Pos_Param16, Pos_Ret19), Time15) :-
28402       holds_at(pos(Pos_Param16, Pos_Ret19), Time15+1),
28403       not(holds_at(pos(Pos_Param17, Pos_Ret19), Time15+1)),
28404       holds_at(pos(Pos_Param17, Pos_Ret19), Time15),
28405       large(Pos_Param17),
28406       large(Pos_Param16),
28407       (   not(equals(Equals_Param18, Pos_Param16))
28408       ;   not(holds_at(abnormalEncroachment(Equals_Param18), Time15))
28409       ).
28410 */
28411axiom(holds_at(pos(Pos_Param16, Pos_Ret19), t),
28412   
28413    [ not(equals(Equals_Param18, Pos_Param16)),
28414      holds_at(pos(Pos_Param16, Pos_Ret19), start),
28415      not(holds_at(pos(Pos_Param17, Pos_Ret19), start)),
28416      holds_at(pos(Pos_Param17, Pos_Ret19), t),
28417      large(Pos_Param17),
28418      large(Pos_Param16),
28419      b(t, start),
28420      ignore(t+1=start)
28421    ]).
28422axiom(holds_at(pos(Pos_Param16, Pos_Ret19), t),
28423   
28424    [ not(holds_at(abnormalEncroachment(Equals_Param18), t)),
28425      holds_at(pos(Pos_Param16, Pos_Ret19), start),
28426      not(holds_at(pos(Pos_Param17, Pos_Ret19), start)),
28427      holds_at(pos(Pos_Param17, Pos_Ret19), t),
28428      large(Pos_Param17),
28429      large(Pos_Param16),
28430      b(t, start),
28431      ignore(t+1=start)
28432    ]).
28433
28434 /*  not(holds_at(pos(Pos_Param21, Pos_Ret24), Time20+1)) :-
28435       not(holds_at(pos(Pos_Param21, Pos_Ret24), Time20)),
28436       not(holds_at(pos(Pos_Param22, Pos_Ret24), Time20+1)),
28437       holds_at(pos(Pos_Param22, Pos_Ret24), Time20),
28438       large(Pos_Param22),
28439       large(Pos_Param21),
28440       (   not(equals(Equals_Param23, Pos_Param21))
28441       ;   not(holds_at(abnormalEncroachment(Equals_Param23), Time20))
28442       ).
28443 */
28444axiom(not(holds_at(pos(Pos_Param21, Pos_Ret24), start)),
28445   
28446    [ not(equals(Equals_Param23, Pos_Param21)),
28447      not(holds_at(pos(Pos_Param21, Pos_Ret24), t)),
28448      not(holds_at(pos(Pos_Param22, Pos_Ret24), start)),
28449      holds_at(pos(Pos_Param22, Pos_Ret24), t),
28450      large(Pos_Param22),
28451      large(Pos_Param21),
28452      b(t, start),
28453      ignore(t+1=start)
28454    ]).
28455axiom(not(holds_at(pos(Pos_Param21, Pos_Ret24), start)),
28456   
28457    [ not(holds_at(abnormalEncroachment(Equals_Param23), t)),
28458      not(holds_at(pos(Pos_Param21, Pos_Ret24), t)),
28459      not(holds_at(pos(Pos_Param22, Pos_Ret24), start)),
28460      holds_at(pos(Pos_Param22, Pos_Ret24), t),
28461      large(Pos_Param22),
28462      large(Pos_Param21),
28463      b(t, start),
28464      ignore(t+1=start)
28465    ]).
28466
28467 /*  not(large(Pos_Param27)) :-
28468       ( large(Pos_Param28),
28469         (   not(equals(Equals_Param26, Pos_Param28))
28470         ;   not(holds_at(abnormalEncroachment(Equals_Param26),
28471                          Time25))
28472         )
28473       ),
28474       holds_at(pos(Pos_Param27, Pos_Ret29), Time25),
28475       not(holds_at(pos(Pos_Param27, Pos_Ret29), Time25+1)),
28476       not(holds_at(pos(Pos_Param28, Pos_Ret29), Time25)),
28477       holds_at(pos(Pos_Param28, Pos_Ret29), Time25+1).
28478 */
28479axiom(not(large(Pos_Param27)),
28480   
28481    [ not(equals(Equals_Param26, Pos_Param28)),
28482      large(Pos_Param28),
28483      holds_at(pos(Pos_Param27, Pos_Ret29), t),
28484      not(holds_at(pos(Pos_Param27, Pos_Ret29), start)),
28485      not(holds_at(pos(Pos_Param28, Pos_Ret29), t)),
28486      holds_at(pos(Pos_Param28, Pos_Ret29), start),
28487      b(t, start),
28488      ignore(t+1=start)
28489    ]).
28490axiom(not(large(Pos_Param27)),
28491   
28492    [ not(holds_at(abnormalEncroachment(Equals_Param26), t)),
28493      large(Pos_Param28),
28494      holds_at(pos(Pos_Param27, Pos_Ret29), t),
28495      not(holds_at(pos(Pos_Param27, Pos_Ret29), start)),
28496      not(holds_at(pos(Pos_Param28, Pos_Ret29), t)),
28497      holds_at(pos(Pos_Param28, Pos_Ret29), start),
28498      b(t, start),
28499      ignore(t+1=start)
28500    ]).
28501
28502 /*  not(large(Pos_Param33)) :-
28503       (   not(equals(Equals_Param31, Pos_Param33))
28504       ;   not(holds_at(abnormalEncroachment(Equals_Param31), Time30))
28505       ),
28506       large(Pos_Param32),
28507       holds_at(pos(Pos_Param32, Pos_Ret34), Time30),
28508       not(holds_at(pos(Pos_Param32, Pos_Ret34), Time30+1)),
28509       not(holds_at(pos(Pos_Param33, Pos_Ret34), Time30)),
28510       holds_at(pos(Pos_Param33, Pos_Ret34), Time30+1).
28511 */
28512axiom(not(large(Pos_Param33)),
28513   
28514    [ not(equals(Equals_Param31, Pos_Param33)),
28515      large(Pos_Param32),
28516      holds_at(pos(Pos_Param32, Pos_Ret34), t),
28517      not(holds_at(pos(Pos_Param32, Pos_Ret34), start)),
28518      not(holds_at(pos(Pos_Param33, Pos_Ret34), t)),
28519      holds_at(pos(Pos_Param33, Pos_Ret34), start),
28520      b(t, start),
28521      ignore(t+1=start)
28522    ]).
28523axiom(not(large(Pos_Param33)),
28524   
28525    [ not(holds_at(abnormalEncroachment(Equals_Param31), t)),
28526      large(Pos_Param32),
28527      holds_at(pos(Pos_Param32, Pos_Ret34), t),
28528      not(holds_at(pos(Pos_Param32, Pos_Ret34), start)),
28529      not(holds_at(pos(Pos_Param33, Pos_Ret34), t)),
28530      holds_at(pos(Pos_Param33, Pos_Ret34), start),
28531      b(t, start),
28532      ignore(t+1=start)
28533    ]).
28534
28535 /*  equals(Equals_Param36, Pos_Param38) :-
28536       large(Pos_Param38),
28537       large(Pos_Param37),
28538       holds_at(pos(Pos_Param37, Pos_Ret39), Time35),
28539       not(holds_at(pos(Pos_Param37, Pos_Ret39), Time35+1)),
28540       not(holds_at(pos(Pos_Param38, Pos_Ret39), Time35)),
28541       holds_at(pos(Pos_Param38, Pos_Ret39), Time35+1).
28542 */
28543axiom(equals(Equals_Param36, Pos_Param38),
28544   
28545    [ large(Pos_Param38),
28546      large(Pos_Param37),
28547      holds_at(pos(Pos_Param37, Pos_Ret39), t),
28548      not(holds_at(pos(Pos_Param37, Pos_Ret39), start)),
28549      not(holds_at(pos(Pos_Param38, Pos_Ret39), t)),
28550      holds_at(pos(Pos_Param38, Pos_Ret39), start),
28551      b(t, start),
28552      ignore(t+1=start)
28553    ]).
28554
28555 /*  holds_at(abnormalEncroachment(AbnormalEncroachment_Ret), Time40) :-
28556       large(Pos_Param42),
28557       large(Pos_Param41),
28558       holds_at(pos(Pos_Param41, Pos_Ret44), Time40),
28559       not(holds_at(pos(Pos_Param41, Pos_Ret44), Time40+1)),
28560       not(holds_at(pos(Pos_Param42, Pos_Ret44), Time40)),
28561       holds_at(pos(Pos_Param42, Pos_Ret44), Time40+1).
28562 */
28563axiom(holds_at(abnormalEncroachment(AbnormalEncroachment_Ret), t),
28564   
28565    [ large(Pos_Param42),
28566      large(Pos_Param41),
28567      holds_at(pos(Pos_Param41, Pos_Ret44), t),
28568      not(holds_at(pos(Pos_Param41, Pos_Ret44), start)),
28569      not(holds_at(pos(Pos_Param42, Pos_Ret44), t)),
28570      holds_at(pos(Pos_Param42, Pos_Ret44), start),
28571      b(t, start),
28572      ignore(t+1=start)
28573    ]).
28574
28575
28576% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8664
28577% [animal1,animal2,position1,position2,time]
28578% animal1!=% animal2 &
28579% Large(animal1) & Large(animal2) &
28580% HoldsAt(Pos(animal1,position1),time) &
28581% HoldsAt(Pos(animal1,position2),time+1) &
28582% HoldsAt(Pos(animal2,position1),time) &
28583% HoldsAt(Pos(animal2,position2),time+1) ->
28584% !{gate} Sides(position1,position2,gate).
28585% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8671
28586axiom(not(exists([Gate], sides(Position1, Position2, Gate))),
28587   
28588    [ { dif(Animal1, Animal2)
28589      },
28590      large(Animal1),
28591      large(Animal2),
28592      holds_at(pos(Animal1, Position1), t),
28593      holds_at(pos(Animal1, Position2), start),
28594      holds_at(pos(Animal2, Position1), t),
28595      holds_at(pos(Animal2, Position2), start),
28596      b(t, start),
28597      ignore(t+1=start)
28598    ]).
28599
28600
28601% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8673
28602% [animal1,animal2,position1,position2,time]
28603% animal1!=% animal2 &
28604% Large(animal1) & Large(animal2) &
28605% HoldsAt(Pos(animal1,position1),time) &
28606% HoldsAt(Pos(animal1,position2),time+1) &
28607% HoldsAt(Pos(animal2,position2),time) &
28608% HoldsAt(Pos(animal2,position1),time+1) ->
28609% !{gate} Sides(position1,position2,gate).
28610% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8680
28611axiom(not(exists([Gate], sides(Position1, Position2, Gate))),
28612   
28613    [ { dif(Animal1, Animal2)
28614      },
28615      large(Animal1),
28616      large(Animal2),
28617      holds_at(pos(Animal1, Position1), t),
28618      holds_at(pos(Animal1, Position2), start),
28619      holds_at(pos(Animal2, Position2), t),
28620      holds_at(pos(Animal2, Position1), start),
28621      b(t, start),
28622      ignore(t+1=start)
28623    ]).
28624
28625
28626% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8682
28627% [gate,position1,position2,time]
28628% HoldsAt(Opened(gate),time) &
28629% !HoldsAt(Opened(gate),time+1) &
28630% Sides(position1,position2,gate) ->
28631% !{animal}
28632% HoldsAt(Pos(animal,position1),time) &
28633% HoldsAt(Pos(animal,position2),time+1).
28634% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8688
28635axiom(not(exists([Animal],  (holds_at(pos(Animal, Position1), t), holds_at(pos(Animal, Position2), t+1)))),
28636   
28637    [ holds_at(opened(Gate), t),
28638      not(holds_at(opened(Gate), start)),
28639      sides(Position1, Position2, Gate),
28640      b(t, start),
28641      ignore(t+1=start)
28642    ]).
28643
28644% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8690
28645% gate GateAO
28646% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8691
28647==> t(gate,gateAO).
28648
28649% cage CageA
28650% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8692
28651==> t(cage,cageA).
28652
28653
28654% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8693
28655% Loc(1)=CageA.
28656loc(1,cageA).
28657
28658
28659% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8694
28660% Loc(2)=CageA.
28661loc(2,cageA).
28662
28663
28664% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8695
28665% Loc(3)=CageA.
28666loc(3,cageA).
28667
28668
28669% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8696
28670% Loc(4)=CageA.
28671loc(4,cageA).
28672
28673
28674% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8697
28675% Loc(5)=Outside.
28676loc(5,outside).
28677
28678
28679% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8698
28680% Loc(6)=Outside.
28681loc(6,outside).
28682
28683
28684% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8699
28685% Loc(7)=Outside.
28686loc(7,outside).
28687
28688
28689% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8700
28690% Loc(8)=Outside.
28691loc(8,outside).
28692
28693
28694% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8702
28695% [position1,position2]
28696% Neighbor(position1,position2) <->
28697% ((position1=1 & position2=2) |
28698%  (position1=1 & position2=3) |
28699%  (position1=1 & position2=4) |
28700%  (position1=2 & position2=3) |
28701%  (position1=2 & position2=4) |
28702%  (position1=3 & position2=4) |
28703%  (position1=5 & position2=6) |
28704%  (position1=5 & position2=7) |
28705%  (position1=5 & position2=8) |
28706%  (position1=6 & position2=7) |
28707%  (position1=6 & position2=8) |
28708%  (position1=7 & position2=8) |
28709%  (position2=1 & position1=2) |
28710%  (position2=1 & position1=3) |
28711%  (position2=1 & position1=4) |
28712%  (position2=2 & position1=3) |
28713%  (position2=2 & position1=4) |
28714%  (position2=3 & position1=4) |
28715%  (position2=5 & position1=6) |
28716%  (position2=5 & position1=7) |
28717%  (position2=5 & position1=8) |
28718%  (position2=6 & position1=7) |
28719%  (position2=6 & position1=8) |
28720%  (position2=7 & position1=8) |
28721%  (position1=4 & position2=7) |
28722%  (position2=4 & position1=7)).
28723
28724 /*  neighbor(Position1, Position2) <->
28725       (   Position1=1,
28726           Position2=2
28727       ;   Position1=1,
28728           Position2=3
28729       ;   Position1=1,
28730           Position2=4
28731       ;   Position1=2,
28732           Position2=3
28733       ;   Position1=2,
28734           Position2=4
28735       ;   Position1=3,
28736           Position2=4
28737       ;   Position1=5,
28738           Position2=6
28739       ;   Position1=5,
28740           Position2=7
28741       ;   Position1=5,
28742           Position2=8
28743       ;   Position1=6,
28744           Position2=7
28745       ;   Position1=6,
28746           Position2=8
28747       ;   Position1=7,
28748           Position2=8
28749       ;   Position2=1,
28750           Position1=2
28751       ;   Position2=1,
28752           Position1=3
28753       ;   Position2=1,
28754           Position1=4
28755       ;   Position2=2,
28756           Position1=3
28757       ;   Position2=2,
28758           Position1=4
28759       ;   Position2=3,
28760           Position1=4
28761       ;   Position2=5,
28762           Position1=6
28763       ;   Position2=5,
28764           Position1=7
28765       ;   Position2=5,
28766           Position1=8
28767       ;   Position2=6,
28768           Position1=7
28769       ;   Position2=6,
28770           Position1=8
28771       ;   Position2=7,
28772           Position1=8
28773       ;   Position1=4,
28774           Position2=7
28775       ;   Position2=4,
28776           Position1=7
28777       ).
28778 */
28779% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8729
28780axiom(neighbor(Position1, Position2),
28781    [equals(Position1, 1), equals(Position2, 2)]).
28782axiom(neighbor(Position1, Position2),
28783    [equals(Position1, 1), equals(Position2, 3)]).
28784axiom(neighbor(Position1, Position2),
28785    [equals(Position1, 1), equals(Position2, 4)]).
28786axiom(neighbor(Position1, Position2),
28787    [equals(Position1, 2), equals(Position2, 3)]).
28788axiom(neighbor(Position1, Position2),
28789    [equals(Position1, 2), equals(Position2, 4)]).
28790axiom(neighbor(Position1, Position2),
28791    [equals(Position1, 3), equals(Position2, 4)]).
28792axiom(neighbor(Position1, Position2),
28793    [equals(Position1, 5), equals(Position2, 6)]).
28794axiom(neighbor(Position1, Position2),
28795    [equals(Position1, 5), equals(Position2, 7)]).
28796axiom(neighbor(Position1, Position2),
28797    [equals(Position1, 5), equals(Position2, 8)]).
28798axiom(neighbor(Position1, Position2),
28799    [equals(Position1, 6), equals(Position2, 7)]).
28800axiom(neighbor(Position1, Position2),
28801    [equals(Position1, 6), equals(Position2, 8)]).
28802axiom(neighbor(Position1, Position2),
28803    [equals(Position1, 7), equals(Position2, 8)]).
28804axiom(neighbor(Position1, Position2),
28805    [equals(Position2, 1), equals(Position1, 2)]).
28806axiom(neighbor(Position1, Position2),
28807    [equals(Position2, 1), equals(Position1, 3)]).
28808axiom(neighbor(Position1, Position2),
28809    [equals(Position2, 1), equals(Position1, 4)]).
28810axiom(neighbor(Position1, Position2),
28811    [equals(Position2, 2), equals(Position1, 3)]).
28812axiom(neighbor(Position1, Position2),
28813    [equals(Position2, 2), equals(Position1, 4)]).
28814axiom(neighbor(Position1, Position2),
28815    [equals(Position2, 3), equals(Position1, 4)]).
28816axiom(neighbor(Position1, Position2),
28817    [equals(Position2, 5), equals(Position1, 6)]).
28818axiom(neighbor(Position1, Position2),
28819    [equals(Position2, 5), equals(Position1, 7)]).
28820axiom(neighbor(Position1, Position2),
28821    [equals(Position2, 5), equals(Position1, 8)]).
28822axiom(neighbor(Position1, Position2),
28823    [equals(Position2, 6), equals(Position1, 7)]).
28824axiom(neighbor(Position1, Position2),
28825    [equals(Position2, 6), equals(Position1, 8)]).
28826axiom(neighbor(Position1, Position2),
28827    [equals(Position2, 7), equals(Position1, 8)]).
28828axiom(neighbor(Position1, Position2),
28829    [equals(Position1, 4), equals(Position2, 7)]).
28830axiom(neighbor(Position1, Position2),
28831    [equals(Position2, 4), equals(Position1, 7)]).
28832
28833 /*   if(neighbor(Position1, Position2),
28834          (Position1=1, Position2=2;Position1=1, Position2=3;Position1=1, Position2=4;Position1=2, Position2=3;Position1=2, Position2=4;Position1=3, Position2=4;Position1=5, Position2=6;Position1=5, Position2=7;Position1=5, Position2=8;Position1=6, Position2=7;Position1=6, Position2=8;Position1=7, Position2=8;Position2=1, Position1=2;Position2=1, Position1=3;Position2=1, Position1=4;Position2=2, Position1=3;Position2=2, Position1=4;Position2=3, Position1=4;Position2=5, Position1=6;Position2=5, Position1=7;Position2=5, Position1=8;Position2=6, Position1=7;Position2=6, Position1=8;Position2=7, Position1=8;Position1=4, Position2=7;Position2=4, Position1=7)).
28835 */
28836todo_later(if(neighbor(Position1, Position2),  (Position1=1, Position2=2;Position1=1, Position2=3;Position1=1, Position2=4;Position1=2, Position2=3;Position1=2, Position2=4;Position1=3, Position2=4;Position1=5, Position2=6;Position1=5, Position2=7;Position1=5, Position2=8;Position1=6, Position2=7;Position1=6, Position2=8;Position1=7, Position2=8;Position2=1, Position1=2;Position2=1, Position1=3;Position2=1, Position1=4;Position2=2, Position1=3;Position2=2, Position1=4;Position2=3, Position1=4;Position2=5, Position1=6;Position2=5, Position1=7;Position2=5, Position1=8;Position2=6, Position1=7;Position2=6, Position1=8;Position2=7, Position1=8;Position1=4, Position2=7;Position2=4, Position1=7)), [(not(neighbor(Neighbor_Param, Equals_Param)):-(not(equals(Neighbor_Param, 1));not(equals(Equals_Param, 2))), (not(equals(Neighbor_Param, 1));not(equals(Equals_Param, 3))), (not(equals(Neighbor_Param, 1));not(equals(Equals_Param, 4))), (not(equals(Neighbor_Param, 2));not(equals(Equals_Param, 3))), (not(equals(Neighbor_Param, 2));not(equals(Equals_Param, 4))), (not(equals(Neighbor_Param, 3));not(equals(Equals_Param, 4))), (not(equals(Neighbor_Param, 5));not(equals(Equals_Param, 6))), (not(equals(Neighbor_Param, 5));not(equals(Equals_Param, 7))), (not(equals(Neighbor_Param, 5));not(equals(Equals_Param, 8))), (not(equals(Neighbor_Param, 6));not(equals(Equals_Param, 7))), (not(equals(Neighbor_Param, 6));not(equals(Equals_Param, 8))), (not(equals(Neighbor_Param, 7));not(equals(Equals_Param, 8))), (not(equals(Equals_Param, 1));not(equals(Neighbor_Param, 2))), (not(equals(Equals_Param, 1));not(equals(Neighbor_Param, 3))), (not(equals(Equals_Param, 1));not(equals(Neighbor_Param, 4))), (not(equals(Equals_Param, 2));not(equals(Neighbor_Param, 3))), (not(equals(Equals_Param, 2));not(equals(Neighbor_Param, 4))), (not(equals(Equals_Param, 3));not(equals(Neighbor_Param, 4))), (not(equals(Equals_Param, 5));not(equals(Neighbor_Param, 6))), (not(equals(Equals_Param, 5));not(equals(Neighbor_Param, 7))), (not(equals(Equals_Param, 5));not(equals(Neighbor_Param, 8))), (not(equals(Equals_Param, 6));not(equals(Neighbor_Param, 7))), (not(equals(Equals_Param, 6));not(equals(Neighbor_Param, 8))), (not(equals(Equals_Param, 7));not(equals(Neighbor_Param, 8))), (not(equals(Neighbor_Param, 4));not(equals(Equals_Param, 7))), (not(equals(Equals_Param, 4));not(equals(Neighbor_Param, 7)))),  (equals(Equals_Param4, 1):-((not(equals(Equals_Param4, 1));not(equals(Equals_Param5, 3))), (not(equals(Equals_Param4, 1));not(equals(Equals_Param5, 4))), (not(equals(Equals_Param4, 2));not(equals(Equals_Param5, 3))), (not(equals(Equals_Param4, 2));not(equals(Equals_Param5, 4))), (not(equals(Equals_Param4, 3));not(equals(Equals_Param5, 4))), (not(equals(Equals_Param4, 5));not(equals(Equals_Param5, 6))), (not(equals(Equals_Param4, 5));not(equals(Equals_Param5, 7))), (not(equals(Equals_Param4, 5));not(equals(Equals_Param5, 8))), (not(equals(Equals_Param4, 6));not(equals(Equals_Param5, 7))), (not(equals(Equals_Param4, 6));not(equals(Equals_Param5, 8))), (not(equals(Equals_Param4, 7));not(equals(Equals_Param5, 8))), (not(equals(Equals_Param5, 1));not(equals(Equals_Param4, 2))), (not(equals(Equals_Param5, 1));not(equals(Equals_Param4, 3))), (not(equals(Equals_Param5, 1));not(equals(Equals_Param4, 4))), (not(equals(Equals_Param5, 2));not(equals(Equals_Param4, 3))), (not(equals(Equals_Param5, 2));not(equals(Equals_Param4, 4))), (not(equals(Equals_Param5, 3));not(equals(Equals_Param4, 4))), (not(equals(Equals_Param5, 5));not(equals(Equals_Param4, 6))), (not(equals(Equals_Param5, 5));not(equals(Equals_Param4, 7))), (not(equals(Equals_Param5, 5));not(equals(Equals_Param4, 8))), (not(equals(Equals_Param5, 6));not(equals(Equals_Param4, 7))), (not(equals(Equals_Param5, 6));not(equals(Equals_Param4, 8))), (not(equals(Equals_Param5, 7));not(equals(Equals_Param4, 8))), (not(equals(Equals_Param4, 4));not(equals(Equals_Param5, 7))), (not(equals(Equals_Param5, 4));not(equals(Equals_Param4, 7)))), neighbor(Equals_Param4, Equals_Param5)),  (equals(Equals_Param6, 2):-((not(equals(Equals_Param7, 1));not(equals(Equals_Param6, 3))), (not(equals(Equals_Param7, 1));not(equals(Equals_Param6, 4))), (not(equals(Equals_Param7, 2));not(equals(Equals_Param6, 3))), (not(equals(Equals_Param7, 2));not(equals(Equals_Param6, 4))), (not(equals(Equals_Param7, 3));not(equals(Equals_Param6, 4))), (not(equals(Equals_Param7, 5));not(equals(Equals_Param6, 6))), (not(equals(Equals_Param7, 5));not(equals(Equals_Param6, 7))), (not(equals(Equals_Param7, 5));not(equals(Equals_Param6, 8))), (not(equals(Equals_Param7, 6));not(equals(Equals_Param6, 7))), (not(equals(Equals_Param7, 6));not(equals(Equals_Param6, 8))), (not(equals(Equals_Param7, 7));not(equals(Equals_Param6, 8))), (not(equals(Equals_Param6, 1));not(equals(Equals_Param7, 2))), (not(equals(Equals_Param6, 1));not(equals(Equals_Param7, 3))), (not(equals(Equals_Param6, 1));not(equals(Equals_Param7, 4))), (not(equals(Equals_Param6, 2));not(equals(Equals_Param7, 3))), (not(equals(Equals_Param6, 2));not(equals(Equals_Param7, 4))), (not(equals(Equals_Param6, 3));not(equals(Equals_Param7, 4))), (not(equals(Equals_Param6, 5));not(equals(Equals_Param7, 6))), (not(equals(Equals_Param6, 5));not(equals(Equals_Param7, 7))), (not(equals(Equals_Param6, 5));not(equals(Equals_Param7, 8))), (not(equals(Equals_Param6, 6));not(equals(Equals_Param7, 7))), (not(equals(Equals_Param6, 6));not(equals(Equals_Param7, 8))), (not(equals(Equals_Param6, 7));not(equals(Equals_Param7, 8))), (not(equals(Equals_Param7, 4));not(equals(Equals_Param6, 7))), (not(equals(Equals_Param6, 4));not(equals(Equals_Param7, 7)))), neighbor(Equals_Param7, Equals_Param6)),  (equals(Equals_Param8, 1):-((not(equals(Equals_Param8, 1));not(equals(Equals_Param9, 4))), (not(equals(Equals_Param8, 2));not(equals(Equals_Param9, 3))), (not(equals(Equals_Param8, 2));not(equals(Equals_Param9, 4))), (not(equals(Equals_Param8, 3));not(equals(Equals_Param9, 4))), (not(equals(Equals_Param8, 5));not(equals(Equals_Param9, 6))), (not(equals(Equals_Param8, 5));not(equals(Equals_Param9, 7))), (not(equals(Equals_Param8, 5));not(equals(Equals_Param9, 8))), (not(equals(Equals_Param8, 6));not(equals(Equals_Param9, 7))), (not(equals(Equals_Param8, 6));not(equals(Equals_Param9, 8))), (not(equals(Equals_Param8, 7));not(equals(Equals_Param9, 8))), (not(equals(Equals_Param9, 1));not(equals(Equals_Param8, 2))), (not(equals(Equals_Param9, 1));not(equals(Equals_Param8, 3))), (not(equals(Equals_Param9, 1));not(equals(Equals_Param8, 4))), (not(equals(Equals_Param9, 2));not(equals(Equals_Param8, 3))), (not(equals(Equals_Param9, 2));not(equals(Equals_Param8, 4))), (not(equals(Equals_Param9, 3));not(equals(Equals_Param8, 4))), (not(equals(Equals_Param9, 5));not(equals(Equals_Param8, 6))), (not(equals(Equals_Param9, 5));not(equals(Equals_Param8, 7))), (not(equals(Equals_Param9, 5));not(equals(Equals_Param8, 8))), (not(equals(Equals_Param9, 6));not(equals(Equals_Param8, 7))), (not(equals(Equals_Param9, 6));not(equals(Equals_Param8, 8))), (not(equals(Equals_Param9, 7));not(equals(Equals_Param8, 8))), (not(equals(Equals_Param8, 4));not(equals(Equals_Param9, 7))), (not(equals(Equals_Param9, 4));not(equals(Equals_Param8, 7)))), (not(equals(Equals_Param8, 1));not(equals(Equals_Param9, 2))), neighbor(Equals_Param8, Equals_Param9)),  (equals(Equals_Param10, 3):-((not(equals(Equals_Param11, 1));not(equals(Equals_Param10, 4))), (not(equals(Equals_Param11, 2));not(equals(Equals_Param10, 3))), (not(equals(Equals_Param11, 2));not(equals(Equals_Param10, 4))), (not(equals(Equals_Param11, 3));not(equals(Equals_Param10, 4))), (not(equals(Equals_Param11, 5));not(equals(Equals_Param10, 6))), (not(equals(Equals_Param11, 5));not(equals(Equals_Param10, 7))), (not(equals(Equals_Param11, 5));not(equals(Equals_Param10, 8))), (not(equals(Equals_Param11, 6));not(equals(Equals_Param10, 7))), (not(equals(Equals_Param11, 6));not(equals(Equals_Param10, 8))), (not(equals(Equals_Param11, 7));not(equals(Equals_Param10, 8))), (not(equals(Equals_Param10, 1));not(equals(Equals_Param11, 2))), (not(equals(Equals_Param10, 1));not(equals(Equals_Param11, 3))), (not(equals(Equals_Param10, 1));not(equals(Equals_Param11, 4))), (not(equals(Equals_Param10, 2));not(equals(Equals_Param11, 3))), (not(equals(Equals_Param10, 2));not(equals(Equals_Param11, 4))), (not(equals(Equals_Param10, 3));not(equals(Equals_Param11, 4))), (not(equals(Equals_Param10, 5));not(equals(Equals_Param11, 6))), (not(equals(Equals_Param10, 5));not(equals(Equals_Param11, 7))), (not(equals(Equals_Param10, 5));not(equals(Equals_Param11, 8))), (not(equals(Equals_Param10, 6));not(equals(Equals_Param11, 7))), (not(equals(Equals_Param10, 6));not(equals(Equals_Param11, 8))), (not(equals(Equals_Param10, 7));not(equals(Equals_Param11, 8))), (not(equals(Equals_Param11, 4));not(equals(Equals_Param10, 7))), (not(equals(Equals_Param10, 4));not(equals(Equals_Param11, 7)))), (not(equals(Equals_Param11, 1));not(equals(Equals_Param10, 2))), neighbor(Equals_Param11, Equals_Param10)),  (equals(Equals_Param12, 1):-((not(equals(Equals_Param12, 2));not(equals(Equals_Param13, 3))), (not(equals(Equals_Param12, 2));not(equals(Equals_Param13, 4))), (not(equals(Equals_Param12, 3));not(equals(Equals_Param13, 4))), (not(equals(Equals_Param12, 5));not(equals(Equals_Param13, 6))), (not(equals(Equals_Param12, 5));not(equals(Equals_Param13, 7))), (not(equals(Equals_Param12, 5));not(equals(Equals_Param13, 8))), (not(equals(Equals_Param12, 6));not(equals(Equals_Param13, 7))), (not(equals(Equals_Param12, 6));not(equals(Equals_Param13, 8))), (not(equals(Equals_Param12, 7));not(equals(Equals_Param13, 8))), (not(equals(Equals_Param13, 1));not(equals(Equals_Param12, 2))), (not(equals(Equals_Param13, 1));not(equals(Equals_Param12, 3))), (not(equals(Equals_Param13, 1));not(equals(Equals_Param12, 4))), (not(equals(Equals_Param13, 2));not(equals(Equals_Param12, 3))), (not(equals(Equals_Param13, 2));not(equals(Equals_Param12, 4))), (not(equals(Equals_Param13, 3));not(equals(Equals_Param12, 4))), (not(equals(Equals_Param13, 5));not(equals(Equals_Param12, 6))), (not(equals(Equals_Param13, 5));not(equals(Equals_Param12, 7))), (not(equals(Equals_Param13, 5));not(equals(Equals_Param12, 8))), (not(equals(Equals_Param13, 6));not(equals(Equals_Param12, 7))), (not(equals(Equals_Param13, 6));not(equals(Equals_Param12, 8))), (not(equals(Equals_Param13, 7));not(equals(Equals_Param12, 8))), (not(equals(Equals_Param12, 4));not(equals(Equals_Param13, 7))), (not(equals(Equals_Param13, 4));not(equals(Equals_Param12, 7)))), (not(equals(Equals_Param12, 1));not(equals(Equals_Param13, 3))), (not(equals(Equals_Param12, 1));not(equals(Equals_Param13, 2))), neighbor(Equals_Param12, Equals_Param13)),  (equals(Equals_Param14, 4):-((not(equals(Equals_Param15, 2));not(equals(Equals_Param14, 3))), (not(equals(Equals_Param15, 2));not(equals(Equals_Param14, 4))), (not(equals(Equals_Param15, 3));not(equals(Equals_Param14, 4))), (not(equals(Equals_Param15, 5));not(equals(Equals_Param14, 6))), (not(equals(Equals_Param15, 5));not(equals(Equals_Param14, 7))), (not(equals(Equals_Param15, 5));not(equals(Equals_Param14, 8))), (not(equals(Equals_Param15, 6));not(equals(Equals_Param14, 7))), (not(equals(Equals_Param15, 6));not(equals(Equals_Param14, 8))), (not(equals(Equals_Param15, 7));not(equals(Equals_Param14, 8))), (not(equals(Equals_Param14, 1));not(equals(Equals_Param15, 2))), (not(equals(Equals_Param14, 1));not(equals(Equals_Param15, 3))), (not(equals(Equals_Param14, 1));not(equals(Equals_Param15, 4))), (not(equals(Equals_Param14, 2));not(equals(Equals_Param15, 3))), (not(equals(Equals_Param14, 2));not(equals(Equals_Param15, 4))), (not(equals(Equals_Param14, 3));not(equals(Equals_Param15, 4))), (not(equals(Equals_Param14, 5));not(equals(Equals_Param15, 6))), (not(equals(Equals_Param14, 5));not(equals(Equals_Param15, 7))), (not(equals(Equals_Param14, 5));not(equals(Equals_Param15, 8))), (not(equals(Equals_Param14, 6));not(equals(Equals_Param15, 7))), (not(equals(Equals_Param14, 6));not(equals(Equals_Param15, 8))), (not(equals(Equals_Param14, 7));not(equals(Equals_Param15, 8))), (not(equals(Equals_Param15, 4));not(equals(Equals_Param14, 7))), (not(equals(Equals_Param14, 4));not(equals(Equals_Param15, 7)))), (not(equals(Equals_Param15, 1));not(equals(Equals_Param14, 3))), (not(equals(Equals_Param15, 1));not(equals(Equals_Param14, 2))), neighbor(Equals_Param15, Equals_Param14)),  (equals(Equals_Param16, 2):-((not(equals(Equals_Param16, 2));not(equals(Equals_Param17, 4))), (not(equals(Equals_Param16, 3));not(equals(Equals_Param17, 4))), (not(equals(Equals_Param16, 5));not(equals(Equals_Param17, 6))), (not(equals(Equals_Param16, 5));not(equals(Equals_Param17, 7))), (not(equals(Equals_Param16, 5));not(equals(Equals_Param17, 8))), (not(equals(Equals_Param16, 6));not(equals(Equals_Param17, 7))), (not(equals(Equals_Param16, 6));not(equals(Equals_Param17, 8))), (not(equals(Equals_Param16, 7));not(equals(Equals_Param17, 8))), (not(equals(Equals_Param17, 1));not(equals(Equals_Param16, 2))), (not(equals(Equals_Param17, 1));not(equals(Equals_Param16, 3))), (not(equals(Equals_Param17, 1));not(equals(Equals_Param16, 4))), (not(equals(Equals_Param17, 2));not(equals(Equals_Param16, 3))), (not(equals(Equals_Param17, 2));not(equals(Equals_Param16, 4))), (not(equals(Equals_Param17, 3));not(equals(Equals_Param16, 4))), (not(equals(Equals_Param17, 5));not(equals(Equals_Param16, 6))), (not(equals(Equals_Param17, 5));not(equals(Equals_Param16, 7))), (not(equals(Equals_Param17, 5));not(equals(Equals_Param16, 8))), (not(equals(Equals_Param17, 6));not(equals(Equals_Param16, 7))), (not(equals(Equals_Param17, 6));not(equals(Equals_Param16, 8))), (not(equals(Equals_Param17, 7));not(equals(Equals_Param16, 8))), (not(equals(Equals_Param16, 4));not(equals(Equals_Param17, 7))), (not(equals(Equals_Param17, 4));not(equals(Equals_Param16, 7)))), (not(equals(Equals_Param16, 1));not(equals(Equals_Param17, 4))), (not(equals(Equals_Param16, 1));not(equals(Equals_Param17, 3))), (not(equals(Equals_Param16, 1));not(equals(Equals_Param17, 2))), neighbor(Equals_Param16, Equals_Param17)),  (equals(Equals_Param18, 3):-((not(equals(Equals_Param19, 2));not(equals(Equals_Param18, 4))), (not(equals(Equals_Param19, 3));not(equals(Equals_Param18, 4))), (not(equals(Equals_Param19, 5));not(equals(Equals_Param18, 6))), (not(equals(Equals_Param19, 5));not(equals(Equals_Param18, 7))), (not(equals(Equals_Param19, 5));not(equals(Equals_Param18, 8))), (not(equals(Equals_Param19, 6));not(equals(Equals_Param18, 7))), (not(equals(Equals_Param19, 6));not(equals(Equals_Param18, 8))), (not(equals(Equals_Param19, 7));not(equals(Equals_Param18, 8))), (not(equals(Equals_Param18, 1));not(equals(Equals_Param19, 2))), (not(equals(Equals_Param18, 1));not(equals(Equals_Param19, 3))), (not(equals(Equals_Param18, 1));not(equals(Equals_Param19, 4))), (not(equals(Equals_Param18, 2));not(equals(Equals_Param19, 3))), (not(equals(Equals_Param18, 2));not(equals(Equals_Param19, 4))), (not(equals(Equals_Param18, 3));not(equals(Equals_Param19, 4))), (not(equals(Equals_Param18, 5));not(equals(Equals_Param19, 6))), (not(equals(Equals_Param18, 5));not(equals(Equals_Param19, 7))), (not(equals(Equals_Param18, 5));not(equals(Equals_Param19, 8))), (not(equals(Equals_Param18, 6));not(equals(Equals_Param19, 7))), (not(equals(Equals_Param18, 6));not(equals(Equals_Param19, 8))), (not(equals(Equals_Param18, 7));not(equals(Equals_Param19, 8))), (not(equals(Equals_Param19, 4));not(equals(Equals_Param18, 7))), (not(equals(Equals_Param18, 4));not(equals(Equals_Param19, 7)))), (not(equals(Equals_Param19, 1));not(equals(Equals_Param18, 4))), (not(equals(Equals_Param19, 1));not(equals(Equals_Param18, 3))), (not(equals(Equals_Param19, 1));not(equals(Equals_Param18, 2))), neighbor(Equals_Param19, Equals_Param18)),  (equals(Equals_Param20, 2):-((not(equals(Equals_Param20, 3));not(equals(Equals_Param21, 4))), (not(equals(Equals_Param20, 5));not(equals(Equals_Param21, 6))), (not(equals(Equals_Param20, 5));not(equals(Equals_Param21, 7))), (not(equals(Equals_Param20, 5));not(equals(Equals_Param21, 8))), (not(equals(Equals_Param20, 6));not(equals(Equals_Param21, 7))), (not(equals(Equals_Param20, 6));not(equals(Equals_Param21, 8))), (not(equals(Equals_Param20, 7));not(equals(Equals_Param21, 8))), (not(equals(Equals_Param21, 1));not(equals(Equals_Param20, 2))), (not(equals(Equals_Param21, 1));not(equals(Equals_Param20, 3))), (not(equals(Equals_Param21, 1));not(equals(Equals_Param20, 4))), (not(equals(Equals_Param21, 2));not(equals(Equals_Param20, 3))), (not(equals(Equals_Param21, 2));not(equals(Equals_Param20, 4))), (not(equals(Equals_Param21, 3));not(equals(Equals_Param20, 4))), (not(equals(Equals_Param21, 5));not(equals(Equals_Param20, 6))), (not(equals(Equals_Param21, 5));not(equals(Equals_Param20, 7))), (not(equals(Equals_Param21, 5));not(equals(Equals_Param20, 8))), (not(equals(Equals_Param21, 6));not(equals(Equals_Param20, 7))), (not(equals(Equals_Param21, 6));not(equals(Equals_Param20, 8))), (not(equals(Equals_Param21, 7));not(equals(Equals_Param20, 8))), (not(equals(Equals_Param20, 4));not(equals(Equals_Param21, 7))), (not(equals(Equals_Param21, 4));not(equals(Equals_Param20, 7)))), (not(equals(Equals_Param20, 2));not(equals(Equals_Param21, 3))), (not(equals(Equals_Param20, 1));not(equals(Equals_Param21, 4))), (not(equals(Equals_Param20, 1));not(equals(Equals_Param21, 3))), (not(equals(Equals_Param20, 1));not(equals(Equals_Param21, 2))), neighbor(Equals_Param20, Equals_Param21)),  (equals(Equals_Param22, 4):-((not(equals(Equals_Param23, 3));not(equals(Equals_Param22, 4))), (not(equals(Equals_Param23, 5));not(equals(Equals_Param22, 6))), (not(equals(Equals_Param23, 5));not(equals(Equals_Param22, 7))), (not(equals(Equals_Param23, 5));not(equals(Equals_Param22, 8))), (not(equals(Equals_Param23, 6));not(equals(Equals_Param22, 7))), (not(equals(Equals_Param23, 6));not(equals(Equals_Param22, 8))), (not(equals(Equals_Param23, 7));not(equals(Equals_Param22, 8))), (not(equals(Equals_Param22, 1));not(equals(Equals_Param23, 2))), (not(equals(Equals_Param22, 1));not(equals(Equals_Param23, 3))), (not(equals(Equals_Param22, 1));not(equals(Equals_Param23, 4))), (not(equals(Equals_Param22, 2));not(equals(Equals_Param23, 3))), (not(equals(Equals_Param22, 2));not(equals(Equals_Param23, 4))), (not(equals(Equals_Param22, 3));not(equals(Equals_Param23, 4))), (not(equals(Equals_Param22, 5));not(equals(Equals_Param23, 6))), (not(equals(Equals_Param22, 5));not(equals(Equals_Param23, 7))), (not(equals(Equals_Param22, 5));not(equals(Equals_Param23, 8))), (not(equals(Equals_Param22, 6));not(equals(Equals_Param23, 7))), (not(equals(Equals_Param22, 6));not(equals(Equals_Param23, 8))), (not(equals(Equals_Param22, 7));not(equals(Equals_Param23, 8))), (not(equals(Equals_Param23, 4));not(equals(Equals_Param22, 7))), (not(equals(Equals_Param22, 4));not(equals(Equals_Param23, 7)))), (not(equals(Equals_Param23, 2));not(equals(Equals_Param22, 3))), (not(equals(Equals_Param23, 1));not(equals(Equals_Param22, 4))), (not(equals(Equals_Param23, 1));not(equals(Equals_Param22, 3))), (not(equals(Equals_Param23, 1));not(equals(Equals_Param22, 2))), neighbor(Equals_Param23, Equals_Param22)),  (equals(Equals_Param24, 3):-((not(equals(Equals_Param24, 5));not(equals(Equals_Param25, 6))), (not(equals(Equals_Param24, 5));not(equals(Equals_Param25, 7))), (not(equals(Equals_Param24, 5));not(equals(Equals_Param25, 8))), (not(equals(Equals_Param24, 6));not(equals(Equals_Param25, 7))), (not(equals(Equals_Param24, 6));not(equals(Equals_Param25, 8))), (not(equals(Equals_Param24, 7));not(equals(Equals_Param25, 8))), (not(equals(Equals_Param25, 1));not(equals(Equals_Param24, 2))), (not(equals(Equals_Param25, 1));not(equals(Equals_Param24, 3))), (not(equals(Equals_Param25, 1));not(equals(Equals_Param24, 4))), (not(equals(Equals_Param25, 2));not(equals(Equals_Param24, 3))), (not(equals(Equals_Param25, 2));not(equals(Equals_Param24, 4))), (not(equals(Equals_Param25, 3));not(equals(Equals_Param24, 4))), (not(equals(Equals_Param25, 5));not(equals(Equals_Param24, 6))), (not(equals(Equals_Param25, 5));not(equals(Equals_Param24, 7))), (not(equals(Equals_Param25, 5));not(equals(Equals_Param24, 8))), (not(equals(Equals_Param25, 6));not(equals(Equals_Param24, 7))), (not(equals(Equals_Param25, 6));not(equals(Equals_Param24, 8))), (not(equals(Equals_Param25, 7));not(equals(Equals_Param24, 8))), (not(equals(Equals_Param24, 4));not(equals(Equals_Param25, 7))), (not(equals(Equals_Param25, 4));not(equals(Equals_Param24, 7)))), (not(equals(Equals_Param24, 2));not(equals(Equals_Param25, 4))), (not(equals(Equals_Param24, 2));not(equals(Equals_Param25, 3))), (not(equals(Equals_Param24, 1));not(equals(Equals_Param25, 4))), (not(equals(Equals_Param24, 1));not(equals(Equals_Param25, 3))), (not(equals(Equals_Param24, 1));not(equals(Equals_Param25, 2))), neighbor(Equals_Param24, Equals_Param25)),  (equals(Equals_Param26, 4):-((not(equals(Equals_Param27, 5));not(equals(Equals_Param26, 6))), (not(equals(Equals_Param27, 5));not(equals(Equals_Param26, 7))), (not(equals(Equals_Param27, 5));not(equals(Equals_Param26, 8))), (not(equals(Equals_Param27, 6));not(equals(Equals_Param26, 7))), (not(equals(Equals_Param27, 6));not(equals(Equals_Param26, 8))), (not(equals(Equals_Param27, 7));not(equals(Equals_Param26, 8))), (not(equals(Equals_Param26, 1));not(equals(Equals_Param27, 2))), (not(equals(Equals_Param26, 1));not(equals(Equals_Param27, 3))), (not(equals(Equals_Param26, 1));not(equals(Equals_Param27, 4))), (not(equals(Equals_Param26, 2));not(equals(Equals_Param27, 3))), (not(equals(Equals_Param26, 2));not(equals(Equals_Param27, 4))), (not(equals(Equals_Param26, 3));not(equals(Equals_Param27, 4))), (not(equals(Equals_Param26, 5));not(equals(Equals_Param27, 6))), (not(equals(Equals_Param26, 5));not(equals(Equals_Param27, 7))), (not(equals(Equals_Param26, 5));not(equals(Equals_Param27, 8))), (not(equals(Equals_Param26, 6));not(equals(Equals_Param27, 7))), (not(equals(Equals_Param26, 6));not(equals(Equals_Param27, 8))), (not(equals(Equals_Param26, 7));not(equals(Equals_Param27, 8))), (not(equals(Equals_Param27, 4));not(equals(Equals_Param26, 7))), (not(equals(Equals_Param26, 4));not(equals(Equals_Param27, 7)))), (not(equals(Equals_Param27, 2));not(equals(Equals_Param26, 4))), (not(equals(Equals_Param27, 2));not(equals(Equals_Param26, 3))), (not(equals(Equals_Param27, 1));not(equals(Equals_Param26, 4))), (not(equals(Equals_Param27, 1));not(equals(Equals_Param26, 3))), (not(equals(Equals_Param27, 1));not(equals(Equals_Param26, 2))), neighbor(Equals_Param27, Equals_Param26)),  (equals(Equals_Param28, 5):-((not(equals(Equals_Param28, 5));not(equals(Equals_Param29, 7))), (not(equals(Equals_Param28, 5));not(equals(Equals_Param29, 8))), (not(equals(Equals_Param28, 6));not(equals(Equals_Param29, 7))), (not(equals(Equals_Param28, 6));not(equals(Equals_Param29, 8))), (not(equals(Equals_Param28, 7));not(equals(Equals_Param29, 8))), (not(equals(Equals_Param29, 1));not(equals(Equals_Param28, 2))), (not(equals(Equals_Param29, 1));not(equals(Equals_Param28, 3))), (not(equals(Equals_Param29, 1));not(equals(Equals_Param28, 4))), (not(equals(Equals_Param29, 2));not(equals(Equals_Param28, 3))), (not(equals(Equals_Param29, 2));not(equals(Equals_Param28, 4))), (not(equals(Equals_Param29, 3));not(equals(Equals_Param28, 4))), (not(equals(Equals_Param29, 5));not(equals(Equals_Param28, 6))), (not(equals(Equals_Param29, 5));not(equals(Equals_Param28, 7))), (not(equals(Equals_Param29, 5));not(equals(Equals_Param28, 8))), (not(equals(Equals_Param29, 6));not(equals(Equals_Param28, 7))), (not(equals(Equals_Param29, 6));not(equals(Equals_Param28, 8))), (not(equals(Equals_Param29, 7));not(equals(Equals_Param28, 8))), (not(equals(Equals_Param28, 4));not(equals(Equals_Param29, 7))), (not(equals(Equals_Param29, 4));not(equals(Equals_Param28, 7)))), (not(equals(Equals_Param28, 3));not(equals(Equals_Param29, 4))), (not(equals(Equals_Param28, 2));not(equals(Equals_Param29, 4))), (not(equals(Equals_Param28, 2));not(equals(Equals_Param29, 3))), (not(equals(Equals_Param28, 1));not(equals(Equals_Param29, 4))), (not(equals(Equals_Param28, 1));not(equals(Equals_Param29, 3))), (not(equals(Equals_Param28, 1));not(equals(Equals_Param29, 2))), neighbor(Equals_Param28, Equals_Param29)),  (equals(Equals_Param30, 6):-((not(equals(Equals_Param31, 5));not(equals(Equals_Param30, 7))), (not(equals(Equals_Param31, 5));not(equals(Equals_Param30, 8))), (not(equals(Equals_Param31, 6));not(equals(Equals_Param30, 7))), (not(equals(Equals_Param31, 6));not(equals(Equals_Param30, 8))), (not(equals(Equals_Param31, 7));not(equals(Equals_Param30, 8))), (not(equals(Equals_Param30, 1));not(equals(Equals_Param31, 2))), (not(equals(Equals_Param30, 1));not(equals(Equals_Param31, 3))), (not(equals(Equals_Param30, 1));not(equals(Equals_Param31, 4))), (not(equals(Equals_Param30, 2));not(equals(Equals_Param31, 3))), (not(equals(Equals_Param30, 2));not(equals(Equals_Param31, 4))), (not(equals(Equals_Param30, 3));not(equals(Equals_Param31, 4))), (not(equals(Equals_Param30, 5));not(equals(Equals_Param31, 6))), (not(equals(Equals_Param30, 5));not(equals(Equals_Param31, 7))), (not(equals(Equals_Param30, 5));not(equals(Equals_Param31, 8))), (not(equals(Equals_Param30, 6));not(equals(Equals_Param31, 7))), (not(equals(Equals_Param30, 6));not(equals(Equals_Param31, 8))), (not(equals(Equals_Param30, 7));not(equals(Equals_Param31, 8))), (not(equals(Equals_Param31, 4));not(equals(Equals_Param30, 7))), (not(equals(Equals_Param30, 4));not(equals(Equals_Param31, 7)))), (not(equals(Equals_Param31, 3));not(equals(Equals_Param30, 4))), (not(equals(Equals_Param31, 2));not(equals(Equals_Param30, 4))), (not(equals(Equals_Param31, 2));not(equals(Equals_Param30, 3))), (not(equals(Equals_Param31, 1));not(equals(Equals_Param30, 4))), (not(equals(Equals_Param31, 1));not(equals(Equals_Param30, 3))), (not(equals(Equals_Param31, 1));not(equals(Equals_Param30, 2))), neighbor(Equals_Param31, Equals_Param30)),  (equals(Equals_Param32, 5):-((not(equals(Equals_Param32, 5));not(equals(Equals_Param33, 8))), (not(equals(Equals_Param32, 6));not(equals(Equals_Param33, 7))), (not(equals(Equals_Param32, 6));not(equals(Equals_Param33, 8))), (not(equals(Equals_Param32, 7));not(equals(Equals_Param33, 8))), (not(equals(Equals_Param33, 1));not(equals(Equals_Param32, 2))), (not(equals(Equals_Param33, 1));not(equals(Equals_Param32, 3))), (not(equals(Equals_Param33, 1));not(equals(Equals_Param32, 4))), (not(equals(Equals_Param33, 2));not(equals(Equals_Param32, 3))), (not(equals(Equals_Param33, 2));not(equals(Equals_Param32, 4))), (not(equals(Equals_Param33, 3));not(equals(Equals_Param32, 4))), (not(equals(Equals_Param33, 5));not(equals(Equals_Param32, 6))), (not(equals(Equals_Param33, 5));not(equals(Equals_Param32, 7))), (not(equals(Equals_Param33, 5));not(equals(Equals_Param32, 8))), (not(equals(Equals_Param33, 6));not(equals(Equals_Param32, 7))), (not(equals(Equals_Param33, 6));not(equals(Equals_Param32, 8))), (not(equals(Equals_Param33, 7));not(equals(Equals_Param32, 8))), (not(equals(Equals_Param32, 4));not(equals(Equals_Param33, 7))), (not(equals(Equals_Param33, 4));not(equals(Equals_Param32, 7)))), (not(equals(Equals_Param32, 5));not(equals(Equals_Param33, 6))), (not(equals(Equals_Param32, 3));not(equals(Equals_Param33, 4))), (not(equals(Equals_Param32, 2));not(equals(Equals_Param33, 4))), (not(equals(Equals_Param32, 2));not(equals(Equals_Param33, 3))), (not(equals(Equals_Param32, 1));not(equals(Equals_Param33, 4))), (not(equals(Equals_Param32, 1));not(equals(Equals_Param33, 3))), (not(equals(Equals_Param32, 1));not(equals(Equals_Param33, 2))), neighbor(Equals_Param32, Equals_Param33)),  (equals(Equals_Param34, 7):-((not(equals(Equals_Param35, 5));not(equals(Equals_Param34, 8))), (not(equals(Equals_Param35, 6));not(equals(Equals_Param34, 7))), (not(equals(Equals_Param35, 6));not(equals(Equals_Param34, 8))), (not(equals(Equals_Param35, 7));not(equals(Equals_Param34, 8))), (not(equals(Equals_Param34, 1));not(equals(Equals_Param35, 2))), (not(equals(Equals_Param34, 1));not(equals(Equals_Param35, 3))), (not(equals(Equals_Param34, 1));not(equals(Equals_Param35, 4))), (not(equals(Equals_Param34, 2));not(equals(Equals_Param35, 3))), (not(equals(Equals_Param34, 2));not(equals(Equals_Param35, 4))), (not(equals(Equals_Param34, 3));not(equals(Equals_Param35, 4))), (not(equals(Equals_Param34, 5));not(equals(Equals_Param35, 6))), (not(equals(Equals_Param34, 5));not(equals(Equals_Param35, 7))), (not(equals(Equals_Param34, 5));not(equals(Equals_Param35, 8))), (not(equals(Equals_Param34, 6));not(equals(Equals_Param35, 7))), (not(equals(Equals_Param34, 6));not(equals(Equals_Param35, 8))), (not(equals(Equals_Param34, 7));not(equals(Equals_Param35, 8))), (not(equals(Equals_Param35, 4));not(equals(Equals_Param34, 7))), (not(equals(Equals_Param34, 4));not(equals(Equals_Param35, 7)))), (not(equals(Equals_Param35, 5));not(equals(Equals_Param34, 6))), (not(equals(Equals_Param35, 3));not(equals(Equals_Param34, 4))), (not(equals(Equals_Param35, 2));not(equals(Equals_Param34, 4))), (not(equals(Equals_Param35, 2));not(equals(Equals_Param34, 3))), (not(equals(Equals_Param35, 1));not(equals(Equals_Param34, 4))), (not(equals(Equals_Param35, 1));not(equals(Equals_Param34, 3))), (not(equals(Equals_Param35, 1));not(equals(Equals_Param34, 2))), neighbor(Equals_Param35, Equals_Param34)),  (equals(Equals_Param36, 5):-((not(equals(Equals_Param36, 6));not(equals(Equals_Param37, 7))), (not(equals(Equals_Param36, 6));not(equals(Equals_Param37, 8))), (not(equals(Equals_Param36, 7));not(equals(Equals_Param37, 8))), (not(equals(Equals_Param37, 1));not(equals(Equals_Param36, 2))), (not(equals(Equals_Param37, 1));not(equals(Equals_Param36, 3))), (not(equals(Equals_Param37, 1));not(equals(Equals_Param36, 4))), (not(equals(Equals_Param37, 2));not(equals(Equals_Param36, 3))), (not(equals(Equals_Param37, 2));not(equals(Equals_Param36, 4))), (not(equals(Equals_Param37, 3));not(equals(Equals_Param36, 4))), (not(equals(Equals_Param37, 5));not(equals(Equals_Param36, 6))), (not(equals(Equals_Param37, 5));not(equals(Equals_Param36, 7))), (not(equals(Equals_Param37, 5));not(equals(Equals_Param36, 8))), (not(equals(Equals_Param37, 6));not(equals(Equals_Param36, 7))), (not(equals(Equals_Param37, 6));not(equals(Equals_Param36, 8))), (not(equals(Equals_Param37, 7));not(equals(Equals_Param36, 8))), (not(equals(Equals_Param36, 4));not(equals(Equals_Param37, 7))), (not(equals(Equals_Param37, 4));not(equals(Equals_Param36, 7)))), (not(equals(Equals_Param36, 5));not(equals(Equals_Param37, 7))), (not(equals(Equals_Param36, 5));not(equals(Equals_Param37, 6))), (not(equals(Equals_Param36, 3));not(equals(Equals_Param37, 4))), (not(equals(Equals_Param36, 2));not(equals(Equals_Param37, 4))), (not(equals(Equals_Param36, 2));not(equals(Equals_Param37, 3))), (not(equals(Equals_Param36, 1));not(equals(Equals_Param37, 4))), (not(equals(Equals_Param36, 1));not(equals(Equals_Param37, 3))), (not(equals(Equals_Param36, 1));not(equals(Equals_Param37, 2))), neighbor(Equals_Param36, Equals_Param37)),  (equals(Equals_Param38, 8):-((not(equals(Equals_Param39, 6));not(equals(Equals_Param38, 7))), (not(equals(Equals_Param39, 6));not(equals(Equals_Param38, 8))), (not(equals(Equals_Param39, 7));not(equals(Equals_Param38, 8))), (not(equals(Equals_Param38, 1));not(equals(Equals_Param39, 2))), (not(equals(Equals_Param38, 1));not(equals(Equals_Param39, 3))), (not(equals(Equals_Param38, 1));not(equals(Equals_Param39, 4))), (not(equals(Equals_Param38, 2));not(equals(Equals_Param39, 3))), (not(equals(Equals_Param38, 2));not(equals(Equals_Param39, 4))), (not(equals(Equals_Param38, 3));not(equals(Equals_Param39, 4))), (not(equals(Equals_Param38, 5));not(equals(Equals_Param39, 6))), (not(equals(Equals_Param38, 5));not(equals(Equals_Param39, 7))), (not(equals(Equals_Param38, 5));not(equals(Equals_Param39, 8))), (not(equals(Equals_Param38, 6));not(equals(Equals_Param39, 7))), (not(equals(Equals_Param38, 6));not(equals(Equals_Param39, 8))), (not(equals(Equals_Param38, 7));not(equals(Equals_Param39, 8))), (not(equals(Equals_Param39, 4));not(equals(Equals_Param38, 7))), (not(equals(Equals_Param38, 4));not(equals(Equals_Param39, 7)))), (not(equals(Equals_Param39, 5));not(equals(Equals_Param38, 7))), (not(equals(Equals_Param39, 5));not(equals(Equals_Param38, 6))), (not(equals(Equals_Param39, 3));not(equals(Equals_Param38, 4))), (not(equals(Equals_Param39, 2));not(equals(Equals_Param38, 4))), (not(equals(Equals_Param39, 2));not(equals(Equals_Param38, 3))), (not(equals(Equals_Param39, 1));not(equals(Equals_Param38, 4))), (not(equals(Equals_Param39, 1));not(equals(Equals_Param38, 3))), (not(equals(Equals_Param39, 1));not(equals(Equals_Param38, 2))), neighbor(Equals_Param39, Equals_Param38)),  (equals(Equals_Param40, 6):-((not(equals(Equals_Param40, 6));not(equals(Equals_Param41, 8))), (not(equals(Equals_Param40, 7));not(equals(Equals_Param41, 8))), (not(equals(Equals_Param41, 1));not(equals(Equals_Param40, 2))), (not(equals(Equals_Param41, 1));not(equals(Equals_Param40, 3))), (not(equals(Equals_Param41, 1));not(equals(Equals_Param40, 4))), (not(equals(Equals_Param41, 2));not(equals(Equals_Param40, 3))), (not(equals(Equals_Param41, 2));not(equals(Equals_Param40, 4))), (not(equals(Equals_Param41, 3));not(equals(Equals_Param40, 4))), (not(equals(Equals_Param41, 5));not(equals(Equals_Param40, 6))), (not(equals(Equals_Param41, 5));not(equals(Equals_Param40, 7))), (not(equals(Equals_Param41, 5));not(equals(Equals_Param40, 8))), (not(equals(Equals_Param41, 6));not(equals(Equals_Param40, 7))), (not(equals(Equals_Param41, 6));not(equals(Equals_Param40, 8))), (not(equals(Equals_Param41, 7));not(equals(Equals_Param40, 8))), (not(equals(Equals_Param40, 4));not(equals(Equals_Param41, 7))), (not(equals(Equals_Param41, 4));not(equals(Equals_Param40, 7)))), (not(equals(Equals_Param40, 5));not(equals(Equals_Param41, 8))), (not(equals(Equals_Param40, 5));not(equals(Equals_Param41, 7))), (not(equals(Equals_Param40, 5));not(equals(Equals_Param41, 6))), (not(equals(Equals_Param40, 3));not(equals(Equals_Param41, 4))), (not(equals(Equals_Param40, 2));not(equals(Equals_Param41, 4))), (not(equals(Equals_Param40, 2));not(equals(Equals_Param41, 3))), (not(equals(Equals_Param40, 1));not(equals(Equals_Param41, 4))), (not(equals(Equals_Param40, 1));not(equals(Equals_Param41, 3))), (not(equals(Equals_Param40, 1));not(equals(Equals_Param41, 2))), neighbor(Equals_Param40, Equals_Param41)),  (equals(Equals_Param42, 7):-((not(equals(Equals_Param43, 6));not(equals(Equals_Param42, 8))), (not(equals(Equals_Param43, 7));not(equals(Equals_Param42, 8))), (not(equals(Equals_Param42, 1));not(equals(Equals_Param43, 2))), (not(equals(Equals_Param42, 1));not(equals(Equals_Param43, 3))), (not(equals(Equals_Param42, 1));not(equals(Equals_Param43, 4))), (not(equals(Equals_Param42, 2));not(equals(Equals_Param43, 3))), (not(equals(Equals_Param42, 2));not(equals(Equals_Param43, 4))), (not(equals(Equals_Param42, 3));not(equals(Equals_Param43, 4))), (not(equals(Equals_Param42, 5));not(equals(Equals_Param43, 6))), (not(equals(Equals_Param42, 5));not(equals(Equals_Param43, 7))), (not(equals(Equals_Param42, 5));not(equals(Equals_Param43, 8))), (not(equals(Equals_Param42, 6));not(equals(Equals_Param43, 7))), (not(equals(Equals_Param42, 6));not(equals(Equals_Param43, 8))), (not(equals(Equals_Param42, 7));not(equals(Equals_Param43, 8))), (not(equals(Equals_Param43, 4));not(equals(Equals_Param42, 7))), (not(equals(Equals_Param42, 4));not(equals(Equals_Param43, 7)))), (not(equals(Equals_Param43, 5));not(equals(Equals_Param42, 8))), (not(equals(Equals_Param43, 5));not(equals(Equals_Param42, 7))), (not(equals(Equals_Param43, 5));not(equals(Equals_Param42, 6))), (not(equals(Equals_Param43, 3));not(equals(Equals_Param42, 4))), (not(equals(Equals_Param43, 2));not(equals(Equals_Param42, 4))), (not(equals(Equals_Param43, 2));not(equals(Equals_Param42, 3))), (not(equals(Equals_Param43, 1));not(equals(Equals_Param42, 4))), (not(equals(Equals_Param43, 1));not(equals(Equals_Param42, 3))), (not(equals(Equals_Param43, 1));not(equals(Equals_Param42, 2))), neighbor(Equals_Param43, Equals_Param42)),  (equals(Equals_Param44, 6):-((not(equals(Equals_Param44, 7));not(equals(Equals_Param45, 8))), (not(equals(Equals_Param45, 1));not(equals(Equals_Param44, 2))), (not(equals(Equals_Param45, 1));not(equals(Equals_Param44, 3))), (not(equals(Equals_Param45, 1));not(equals(Equals_Param44, 4))), (not(equals(Equals_Param45, 2));not(equals(Equals_Param44, 3))), (not(equals(Equals_Param45, 2));not(equals(Equals_Param44, 4))), (not(equals(Equals_Param45, 3));not(equals(Equals_Param44, 4))), (not(equals(Equals_Param45, 5));not(equals(Equals_Param44, 6))), (not(equals(Equals_Param45, 5));not(equals(Equals_Param44, 7))), (not(equals(Equals_Param45, 5));not(equals(Equals_Param44, 8))), (not(equals(Equals_Param45, 6));not(equals(Equals_Param44, 7))), (not(equals(Equals_Param45, 6));not(equals(Equals_Param44, 8))), (not(equals(Equals_Param45, 7));not(equals(Equals_Param44, 8))), (not(equals(Equals_Param44, 4));not(equals(Equals_Param45, 7))), (not(equals(Equals_Param45, 4));not(equals(Equals_Param44, 7)))), (not(equals(Equals_Param44, 6));not(equals(Equals_Param45, 7))), (not(equals(Equals_Param44, 5));not(equals(Equals_Param45, 8))), (not(equals(Equals_Param44, 5));not(equals(Equals_Param45, 7))), (not(equals(Equals_Param44, 5));not(equals(Equals_Param45, 6))), (not(equals(Equals_Param44, 3));not(equals(Equals_Param45, 4))), (not(equals(Equals_Param44, 2));not(equals(Equals_Param45, 4))), (not(equals(Equals_Param44, 2));not(equals(Equals_Param45, 3))), (not(equals(Equals_Param44, 1));not(equals(Equals_Param45, 4))), (not(equals(Equals_Param44, 1));not(equals(Equals_Param45, 3))), (not(equals(Equals_Param44, 1));not(equals(Equals_Param45, 2))), neighbor(Equals_Param44, Equals_Param45)),  (equals(Equals_Param46, 8):-((not(equals(Equals_Param47, 7));not(equals(Equals_Param46, 8))), (not(equals(Equals_Param46, 1));not(equals(Equals_Param47, 2))), (not(equals(Equals_Param46, 1));not(equals(Equals_Param47, 3))), (not(equals(Equals_Param46, 1));not(equals(Equals_Param47, 4))), (not(equals(Equals_Param46, 2));not(equals(Equals_Param47, 3))), (not(equals(Equals_Param46, 2));not(equals(Equals_Param47, 4))), (not(equals(Equals_Param46, 3));not(equals(Equals_Param47, 4))), (not(equals(Equals_Param46, 5));not(equals(Equals_Param47, 6))), (not(equals(Equals_Param46, 5));not(equals(Equals_Param47, 7))), (not(equals(Equals_Param46, 5));not(equals(Equals_Param47, 8))), (not(equals(Equals_Param46, 6));not(equals(Equals_Param47, 7))), (not(equals(Equals_Param46, 6));not(equals(Equals_Param47, 8))), (not(equals(Equals_Param46, 7));not(equals(Equals_Param47, 8))), (not(equals(Equals_Param47, 4));not(equals(Equals_Param46, 7))), (not(equals(Equals_Param46, 4));not(equals(Equals_Param47, 7)))), (not(equals(Equals_Param47, 6));not(equals(Equals_Param46, 7))), (not(equals(Equals_Param47, 5));not(equals(Equals_Param46, 8))), (not(equals(Equals_Param47, 5));not(equals(Equals_Param46, 7))), (not(equals(Equals_Param47, 5));not(equals(Equals_Param46, 6))), (not(equals(Equals_Param47, 3));not(equals(Equals_Param46, 4))), (not(equals(Equals_Param47, 2));not(equals(Equals_Param46, 4))), (not(equals(Equals_Param47, 2));not(equals(Equals_Param46, 3))), (not(equals(Equals_Param47, 1));not(equals(Equals_Param46, 4))), (not(equals(Equals_Param47, 1));not(equals(Equals_Param46, 3))), (not(equals(Equals_Param47, 1));not(equals(Equals_Param46, 2))), neighbor(Equals_Param47, Equals_Param46)),  (equals(Equals_Param48, 7):-((not(equals(Equals_Param49, 1));not(equals(Equals_Param48, 2))), (not(equals(Equals_Param49, 1));not(equals(Equals_Param48, 3))), (not(equals(Equals_Param49, 1));not(equals(Equals_Param48, 4))), (not(equals(Equals_Param49, 2));not(equals(Equals_Param48, 3))), (not(equals(Equals_Param49, 2));not(equals(Equals_Param48, 4))), (not(equals(Equals_Param49, 3));not(equals(Equals_Param48, 4))), (not(equals(Equals_Param49, 5));not(equals(Equals_Param48, 6))), (not(equals(Equals_Param49, 5));not(equals(Equals_Param48, 7))), (not(equals(Equals_Param49, 5));not(equals(Equals_Param48, 8))), (not(equals(Equals_Param49, 6));not(equals(Equals_Param48, 7))), (not(equals(Equals_Param49, 6));not(equals(Equals_Param48, 8))), (not(equals(Equals_Param49, 7));not(equals(Equals_Param48, 8))), (not(equals(Equals_Param48, 4));not(equals(Equals_Param49, 7))), (not(equals(Equals_Param49, 4));not(equals(Equals_Param48, 7)))), (not(equals(Equals_Param48, 6));not(equals(Equals_Param49, 8))), (not(equals(Equals_Param48, 6));not(equals(Equals_Param49, 7))), (not(equals(Equals_Param48, 5));not(equals(Equals_Param49, 8))), (not(equals(Equals_Param48, 5));not(equals(Equals_Param49, 7))), (not(equals(Equals_Param48, 5));not(equals(Equals_Param49, 6))), (not(equals(Equals_Param48, 3));not(equals(Equals_Param49, 4))), (not(equals(Equals_Param48, 2));not(equals(Equals_Param49, 4))), (not(equals(Equals_Param48, 2));not(equals(Equals_Param49, 3))), (not(equals(Equals_Param48, 1));not(equals(Equals_Param49, 4))), (not(equals(Equals_Param48, 1));not(equals(Equals_Param49, 3))), (not(equals(Equals_Param48, 1));not(equals(Equals_Param49, 2))), neighbor(Equals_Param48, Equals_Param49)),  (equals(Equals_Param50, 8):-((not(equals(Equals_Param50, 1));not(equals(Equals_Param51, 2))), (not(equals(Equals_Param50, 1));not(equals(Equals_Param51, 3))), (not(equals(Equals_Param50, 1));not(equals(Equals_Param51, 4))), (not(equals(Equals_Param50, 2));not(equals(Equals_Param51, 3))), (not(equals(Equals_Param50, 2));not(equals(Equals_Param51, 4))), (not(equals(Equals_Param50, 3));not(equals(Equals_Param51, 4))), (not(equals(Equals_Param50, 5));not(equals(Equals_Param51, 6))), (not(equals(Equals_Param50, 5));not(equals(Equals_Param51, 7))), (not(equals(Equals_Param50, 5));not(equals(Equals_Param51, 8))), (not(equals(Equals_Param50, 6));not(equals(Equals_Param51, 7))), (not(equals(Equals_Param50, 6));not(equals(Equals_Param51, 8))), (not(equals(Equals_Param50, 7));not(equals(Equals_Param51, 8))), (not(equals(Equals_Param51, 4));not(equals(Equals_Param50, 7))), (not(equals(Equals_Param50, 4));not(equals(Equals_Param51, 7)))), (not(equals(Equals_Param51, 6));not(equals(Equals_Param50, 8))), (not(equals(Equals_Param51, 6));not(equals(Equals_Param50, 7))), (not(equals(Equals_Param51, 5));not(equals(Equals_Param50, 8))), (not(equals(Equals_Param51, 5));not(equals(Equals_Param50, 7))), (not(equals(Equals_Param51, 5));not(equals(Equals_Param50, 6))), (not(equals(Equals_Param51, 3));not(equals(Equals_Param50, 4))), (not(equals(Equals_Param51, 2));not(equals(Equals_Param50, 4))), (not(equals(Equals_Param51, 2));not(equals(Equals_Param50, 3))), (not(equals(Equals_Param51, 1));not(equals(Equals_Param50, 4))), (not(equals(Equals_Param51, 1));not(equals(Equals_Param50, 3))), (not(equals(Equals_Param51, 1));not(equals(Equals_Param50, 2))), neighbor(Equals_Param51, Equals_Param50)),  (equals(Equals_Param52, 1):-((not(equals(Equals_Param52, 1));not(equals(Equals_Param53, 3))), (not(equals(Equals_Param52, 1));not(equals(Equals_Param53, 4))), (not(equals(Equals_Param52, 2));not(equals(Equals_Param53, 3))), (not(equals(Equals_Param52, 2));not(equals(Equals_Param53, 4))), (not(equals(Equals_Param52, 3));not(equals(Equals_Param53, 4))), (not(equals(Equals_Param52, 5));not(equals(Equals_Param53, 6))), (not(equals(Equals_Param52, 5));not(equals(Equals_Param53, 7))), (not(equals(Equals_Param52, 5));not(equals(Equals_Param53, 8))), (not(equals(Equals_Param52, 6));not(equals(Equals_Param53, 7))), (not(equals(Equals_Param52, 6));not(equals(Equals_Param53, 8))), (not(equals(Equals_Param52, 7));not(equals(Equals_Param53, 8))), (not(equals(Equals_Param53, 4));not(equals(Equals_Param52, 7))), (not(equals(Equals_Param52, 4));not(equals(Equals_Param53, 7)))), (not(equals(Equals_Param53, 7));not(equals(Equals_Param52, 8))), (not(equals(Equals_Param53, 6));not(equals(Equals_Param52, 8))), (not(equals(Equals_Param53, 6));not(equals(Equals_Param52, 7))), (not(equals(Equals_Param53, 5));not(equals(Equals_Param52, 8))), (not(equals(Equals_Param53, 5));not(equals(Equals_Param52, 7))), (not(equals(Equals_Param53, 5));not(equals(Equals_Param52, 6))), (not(equals(Equals_Param53, 3));not(equals(Equals_Param52, 4))), (not(equals(Equals_Param53, 2));not(equals(Equals_Param52, 4))), (not(equals(Equals_Param53, 2));not(equals(Equals_Param52, 3))), (not(equals(Equals_Param53, 1));not(equals(Equals_Param52, 4))), (not(equals(Equals_Param53, 1));not(equals(Equals_Param52, 3))), (not(equals(Equals_Param53, 1));not(equals(Equals_Param52, 2))), neighbor(Equals_Param53, Equals_Param52)),  (equals(Equals_Param54, 2):-((not(equals(Equals_Param55, 1));not(equals(Equals_Param54, 3))), (not(equals(Equals_Param55, 1));not(equals(Equals_Param54, 4))), (not(equals(Equals_Param55, 2));not(equals(Equals_Param54, 3))), (not(equals(Equals_Param55, 2));not(equals(Equals_Param54, 4))), (not(equals(Equals_Param55, 3));not(equals(Equals_Param54, 4))), (not(equals(Equals_Param55, 5));not(equals(Equals_Param54, 6))), (not(equals(Equals_Param55, 5));not(equals(Equals_Param54, 7))), (not(equals(Equals_Param55, 5));not(equals(Equals_Param54, 8))), (not(equals(Equals_Param55, 6));not(equals(Equals_Param54, 7))), (not(equals(Equals_Param55, 6));not(equals(Equals_Param54, 8))), (not(equals(Equals_Param55, 7));not(equals(Equals_Param54, 8))), (not(equals(Equals_Param54, 4));not(equals(Equals_Param55, 7))), (not(equals(Equals_Param55, 4));not(equals(Equals_Param54, 7)))), (not(equals(Equals_Param54, 7));not(equals(Equals_Param55, 8))), (not(equals(Equals_Param54, 6));not(equals(Equals_Param55, 8))), (not(equals(Equals_Param54, 6));not(equals(Equals_Param55, 7))), (not(equals(Equals_Param54, 5));not(equals(Equals_Param55, 8))), (not(equals(Equals_Param54, 5));not(equals(Equals_Param55, 7))), (not(equals(Equals_Param54, 5));not(equals(Equals_Param55, 6))), (not(equals(Equals_Param54, 3));not(equals(Equals_Param55, 4))), (not(equals(Equals_Param54, 2));not(equals(Equals_Param55, 4))), (not(equals(Equals_Param54, 2));not(equals(Equals_Param55, 3))), (not(equals(Equals_Param54, 1));not(equals(Equals_Param55, 4))), (not(equals(Equals_Param54, 1));not(equals(Equals_Param55, 3))), (not(equals(Equals_Param54, 1));not(equals(Equals_Param55, 2))), neighbor(Equals_Param54, Equals_Param55)),  (equals(Equals_Param56, 1):-((not(equals(Equals_Param56, 1));not(equals(Equals_Param57, 4))), (not(equals(Equals_Param56, 2));not(equals(Equals_Param57, 3))), (not(equals(Equals_Param56, 2));not(equals(Equals_Param57, 4))), (not(equals(Equals_Param56, 3));not(equals(Equals_Param57, 4))), (not(equals(Equals_Param56, 5));not(equals(Equals_Param57, 6))), (not(equals(Equals_Param56, 5));not(equals(Equals_Param57, 7))), (not(equals(Equals_Param56, 5));not(equals(Equals_Param57, 8))), (not(equals(Equals_Param56, 6));not(equals(Equals_Param57, 7))), (not(equals(Equals_Param56, 6));not(equals(Equals_Param57, 8))), (not(equals(Equals_Param56, 7));not(equals(Equals_Param57, 8))), (not(equals(Equals_Param57, 4));not(equals(Equals_Param56, 7))), (not(equals(Equals_Param56, 4));not(equals(Equals_Param57, 7)))), (not(equals(Equals_Param56, 1));not(equals(Equals_Param57, 2))), (not(equals(Equals_Param57, 7));not(equals(Equals_Param56, 8))), (not(equals(Equals_Param57, 6));not(equals(Equals_Param56, 8))), (not(equals(Equals_Param57, 6));not(equals(Equals_Param56, 7))), (not(equals(Equals_Param57, 5));not(equals(Equals_Param56, 8))), (not(equals(Equals_Param57, 5));not(equals(Equals_Param56, 7))), (not(equals(Equals_Param57, 5));not(equals(Equals_Param56, 6))), (not(equals(Equals_Param57, 3));not(equals(Equals_Param56, 4))), (not(equals(Equals_Param57, 2));not(equals(Equals_Param56, 4))), (not(equals(Equals_Param57, 2));not(equals(Equals_Param56, 3))), (not(equals(Equals_Param57, 1));not(equals(Equals_Param56, 4))), (not(equals(Equals_Param57, 1));not(equals(Equals_Param56, 3))), (not(equals(Equals_Param57, 1));not(equals(Equals_Param56, 2))), neighbor(Equals_Param57, Equals_Param56)),  (equals(Equals_Param58, 3):-((not(equals(Equals_Param59, 1));not(equals(Equals_Param58, 4))), (not(equals(Equals_Param59, 2));not(equals(Equals_Param58, 3))), (not(equals(Equals_Param59, 2));not(equals(Equals_Param58, 4))), (not(equals(Equals_Param59, 3));not(equals(Equals_Param58, 4))), (not(equals(Equals_Param59, 5));not(equals(Equals_Param58, 6))), (not(equals(Equals_Param59, 5));not(equals(Equals_Param58, 7))), (not(equals(Equals_Param59, 5));not(equals(Equals_Param58, 8))), (not(equals(Equals_Param59, 6));not(equals(Equals_Param58, 7))), (not(equals(Equals_Param59, 6));not(equals(Equals_Param58, 8))), (not(equals(Equals_Param59, 7));not(equals(Equals_Param58, 8))), (not(equals(Equals_Param58, 4));not(equals(Equals_Param59, 7))), (not(equals(Equals_Param59, 4));not(equals(Equals_Param58, 7)))), (not(equals(Equals_Param59, 1));not(equals(Equals_Param58, 2))), (not(equals(Equals_Param58, 7));not(equals(Equals_Param59, 8))), (not(equals(Equals_Param58, 6));not(equals(Equals_Param59, 8))), (not(equals(Equals_Param58, 6));not(equals(Equals_Param59, 7))), (not(equals(Equals_Param58, 5));not(equals(Equals_Param59, 8))), (not(equals(Equals_Param58, 5));not(equals(Equals_Param59, 7))), (not(equals(Equals_Param58, 5));not(equals(Equals_Param59, 6))), (not(equals(Equals_Param58, 3));not(equals(Equals_Param59, 4))), (not(equals(Equals_Param58, 2));not(equals(Equals_Param59, 4))), (not(equals(Equals_Param58, 2));not(equals(Equals_Param59, 3))), (not(equals(Equals_Param58, 1));not(equals(Equals_Param59, 4))), (not(equals(Equals_Param58, 1));not(equals(Equals_Param59, 3))), (not(equals(Equals_Param58, 1));not(equals(Equals_Param59, 2))), neighbor(Equals_Param58, Equals_Param59)),  (equals(Equals_Param60, 1):-((not(equals(Equals_Param60, 2));not(equals(Equals_Param61, 3))), (not(equals(Equals_Param60, 2));not(equals(Equals_Param61, 4))), (not(equals(Equals_Param60, 3));not(equals(Equals_Param61, 4))), (not(equals(Equals_Param60, 5));not(equals(Equals_Param61, 6))), (not(equals(Equals_Param60, 5));not(equals(Equals_Param61, 7))), (not(equals(Equals_Param60, 5));not(equals(Equals_Param61, 8))), (not(equals(Equals_Param60, 6));not(equals(Equals_Param61, 7))), (not(equals(Equals_Param60, 6));not(equals(Equals_Param61, 8))), (not(equals(Equals_Param60, 7));not(equals(Equals_Param61, 8))), (not(equals(Equals_Param61, 4));not(equals(Equals_Param60, 7))), (not(equals(Equals_Param60, 4));not(equals(Equals_Param61, 7)))), (not(equals(Equals_Param60, 1));not(equals(Equals_Param61, 3))), (not(equals(Equals_Param60, 1));not(equals(Equals_Param61, 2))), (not(equals(Equals_Param61, 7));not(equals(Equals_Param60, 8))), (not(equals(Equals_Param61, 6));not(equals(Equals_Param60, 8))), (not(equals(Equals_Param61, 6));not(equals(Equals_Param60, 7))), (not(equals(Equals_Param61, 5));not(equals(Equals_Param60, 8))), (not(equals(Equals_Param61, 5));not(equals(Equals_Param60, 7))), (not(equals(Equals_Param61, 5));not(equals(Equals_Param60, 6))), (not(equals(Equals_Param61, 3));not(equals(Equals_Param60, 4))), (not(equals(Equals_Param61, 2));not(equals(Equals_Param60, 4))), (not(equals(Equals_Param61, 2));not(equals(Equals_Param60, 3))), (not(equals(Equals_Param61, 1));not(equals(Equals_Param60, 4))), (not(equals(Equals_Param61, 1));not(equals(Equals_Param60, 3))), (not(equals(Equals_Param61, 1));not(equals(Equals_Param60, 2))), neighbor(Equals_Param61, Equals_Param60)),  (equals(Equals_Param62, 4):-((not(equals(Equals_Param63, 2));not(equals(Equals_Param62, 3))), (not(equals(Equals_Param63, 2));not(equals(Equals_Param62, 4))), (not(equals(Equals_Param63, 3));not(equals(Equals_Param62, 4))), (not(equals(Equals_Param63, 5));not(equals(Equals_Param62, 6))), (not(equals(Equals_Param63, 5));not(equals(Equals_Param62, 7))), (not(equals(Equals_Param63, 5));not(equals(Equals_Param62, 8))), (not(equals(Equals_Param63, 6));not(equals(Equals_Param62, 7))), (not(equals(Equals_Param63, 6));not(equals(Equals_Param62, 8))), (not(equals(Equals_Param63, 7));not(equals(Equals_Param62, 8))), (not(equals(Equals_Param62, 4));not(equals(Equals_Param63, 7))), (not(equals(Equals_Param63, 4));not(equals(Equals_Param62, 7)))), (not(equals(Equals_Param63, 1));not(equals(Equals_Param62, 3))), (not(equals(Equals_Param63, 1));not(equals(Equals_Param62, 2))), (not(equals(Equals_Param62, 7));not(equals(Equals_Param63, 8))), (not(equals(Equals_Param62, 6));not(equals(Equals_Param63, 8))), (not(equals(Equals_Param62, 6));not(equals(Equals_Param63, 7))), (not(equals(Equals_Param62, 5));not(equals(Equals_Param63, 8))), (not(equals(Equals_Param62, 5));not(equals(Equals_Param63, 7))), (not(equals(Equals_Param62, 5));not(equals(Equals_Param63, 6))), (not(equals(Equals_Param62, 3));not(equals(Equals_Param63, 4))), (not(equals(Equals_Param62, 2));not(equals(Equals_Param63, 4))), (not(equals(Equals_Param62, 2));not(equals(Equals_Param63, 3))), (not(equals(Equals_Param62, 1));not(equals(Equals_Param63, 4))), (not(equals(Equals_Param62, 1));not(equals(Equals_Param63, 3))), (not(equals(Equals_Param62, 1));not(equals(Equals_Param63, 2))), neighbor(Equals_Param62, Equals_Param63)),  (equals(Equals_Param64, 2):-((not(equals(Equals_Param64, 2));not(equals(Equals_Param65, 4))), (not(equals(Equals_Param64, 3));not(equals(Equals_Param65, 4))), (not(equals(Equals_Param64, 5));not(equals(Equals_Param65, 6))), (not(equals(Equals_Param64, 5));not(equals(Equals_Param65, 7))), (not(equals(Equals_Param64, 5));not(equals(Equals_Param65, 8))), (not(equals(Equals_Param64, 6));not(equals(Equals_Param65, 7))), (not(equals(Equals_Param64, 6));not(equals(Equals_Param65, 8))), (not(equals(Equals_Param64, 7));not(equals(Equals_Param65, 8))), (not(equals(Equals_Param65, 4));not(equals(Equals_Param64, 7))), (not(equals(Equals_Param64, 4));not(equals(Equals_Param65, 7)))), (not(equals(Equals_Param64, 1));not(equals(Equals_Param65, 4))), (not(equals(Equals_Param64, 1));not(equals(Equals_Param65, 3))), (not(equals(Equals_Param64, 1));not(equals(Equals_Param65, 2))), (not(equals(Equals_Param65, 7));not(equals(Equals_Param64, 8))), (not(equals(Equals_Param65, 6));not(equals(Equals_Param64, 8))), (not(equals(Equals_Param65, 6));not(equals(Equals_Param64, 7))), (not(equals(Equals_Param65, 5));not(equals(Equals_Param64, 8))), (not(equals(Equals_Param65, 5));not(equals(Equals_Param64, 7))), (not(equals(Equals_Param65, 5));not(equals(Equals_Param64, 6))), (not(equals(Equals_Param65, 3));not(equals(Equals_Param64, 4))), (not(equals(Equals_Param65, 2));not(equals(Equals_Param64, 4))), (not(equals(Equals_Param65, 2));not(equals(Equals_Param64, 3))), (not(equals(Equals_Param65, 1));not(equals(Equals_Param64, 4))), (not(equals(Equals_Param65, 1));not(equals(Equals_Param64, 3))), (not(equals(Equals_Param65, 1));not(equals(Equals_Param64, 2))), neighbor(Equals_Param65, Equals_Param64)),  (equals(Equals_Param66, 3):-((not(equals(Equals_Param67, 2));not(equals(Equals_Param66, 4))), (not(equals(Equals_Param67, 3));not(equals(Equals_Param66, 4))), (not(equals(Equals_Param67, 5));not(equals(Equals_Param66, 6))), (not(equals(Equals_Param67, 5));not(equals(Equals_Param66, 7))), (not(equals(Equals_Param67, 5));not(equals(Equals_Param66, 8))), (not(equals(Equals_Param67, 6));not(equals(Equals_Param66, 7))), (not(equals(Equals_Param67, 6));not(equals(Equals_Param66, 8))), (not(equals(Equals_Param67, 7));not(equals(Equals_Param66, 8))), (not(equals(Equals_Param66, 4));not(equals(Equals_Param67, 7))), (not(equals(Equals_Param67, 4));not(equals(Equals_Param66, 7)))), (not(equals(Equals_Param67, 1));not(equals(Equals_Param66, 4))), (not(equals(Equals_Param67, 1));not(equals(Equals_Param66, 3))), (not(equals(Equals_Param67, 1));not(equals(Equals_Param66, 2))), (not(equals(Equals_Param66, 7));not(equals(Equals_Param67, 8))), (not(equals(Equals_Param66, 6));not(equals(Equals_Param67, 8))), (not(equals(Equals_Param66, 6));not(equals(Equals_Param67, 7))), (not(equals(Equals_Param66, 5));not(equals(Equals_Param67, 8))), (not(equals(Equals_Param66, 5));not(equals(Equals_Param67, 7))), (not(equals(Equals_Param66, 5));not(equals(Equals_Param67, 6))), (not(equals(Equals_Param66, 3));not(equals(Equals_Param67, 4))), (not(equals(Equals_Param66, 2));not(equals(Equals_Param67, 4))), (not(equals(Equals_Param66, 2));not(equals(Equals_Param67, 3))), (not(equals(Equals_Param66, 1));not(equals(Equals_Param67, 4))), (not(equals(Equals_Param66, 1));not(equals(Equals_Param67, 3))), (not(equals(Equals_Param66, 1));not(equals(Equals_Param67, 2))), neighbor(Equals_Param66, Equals_Param67)),  (equals(Equals_Param68, 2):-((not(equals(Equals_Param68, 3));not(equals(Equals_Param69, 4))), (not(equals(Equals_Param68, 5));not(equals(Equals_Param69, 6))), (not(equals(Equals_Param68, 5));not(equals(Equals_Param69, 7))), (not(equals(Equals_Param68, 5));not(equals(Equals_Param69, 8))), (not(equals(Equals_Param68, 6));not(equals(Equals_Param69, 7))), (not(equals(Equals_Param68, 6));not(equals(Equals_Param69, 8))), (not(equals(Equals_Param68, 7));not(equals(Equals_Param69, 8))), (not(equals(Equals_Param69, 4));not(equals(Equals_Param68, 7))), (not(equals(Equals_Param68, 4));not(equals(Equals_Param69, 7)))), (not(equals(Equals_Param68, 2));not(equals(Equals_Param69, 3))), (not(equals(Equals_Param68, 1));not(equals(Equals_Param69, 4))), (not(equals(Equals_Param68, 1));not(equals(Equals_Param69, 3))), (not(equals(Equals_Param68, 1));not(equals(Equals_Param69, 2))), (not(equals(Equals_Param69, 7));not(equals(Equals_Param68, 8))), (not(equals(Equals_Param69, 6));not(equals(Equals_Param68, 8))), (not(equals(Equals_Param69, 6));not(equals(Equals_Param68, 7))), (not(equals(Equals_Param69, 5));not(equals(Equals_Param68, 8))), (not(equals(Equals_Param69, 5));not(equals(Equals_Param68, 7))), (not(equals(Equals_Param69, 5));not(equals(Equals_Param68, 6))), (not(equals(Equals_Param69, 3));not(equals(Equals_Param68, 4))), (not(equals(Equals_Param69, 2));not(equals(Equals_Param68, 4))), (not(equals(Equals_Param69, 2));not(equals(Equals_Param68, 3))), (not(equals(Equals_Param69, 1));not(equals(Equals_Param68, 4))), (not(equals(Equals_Param69, 1));not(equals(Equals_Param68, 3))), (not(equals(Equals_Param69, 1));not(equals(Equals_Param68, 2))), neighbor(Equals_Param69, Equals_Param68)),  (equals(Equals_Param70, 4):-((not(equals(Equals_Param71, 3));not(equals(Equals_Param70, 4))), (not(equals(Equals_Param71, 5));not(equals(Equals_Param70, 6))), (not(equals(Equals_Param71, 5));not(equals(Equals_Param70, 7))), (not(equals(Equals_Param71, 5));not(equals(Equals_Param70, 8))), (not(equals(Equals_Param71, 6));not(equals(Equals_Param70, 7))), (not(equals(Equals_Param71, 6));not(equals(Equals_Param70, 8))), (not(equals(Equals_Param71, 7));not(equals(Equals_Param70, 8))), (not(equals(Equals_Param70, 4));not(equals(Equals_Param71, 7))), (not(equals(Equals_Param71, 4));not(equals(Equals_Param70, 7)))), (not(equals(Equals_Param71, 2));not(equals(Equals_Param70, 3))), (not(equals(Equals_Param71, 1));not(equals(Equals_Param70, 4))), (not(equals(Equals_Param71, 1));not(equals(Equals_Param70, 3))), (not(equals(Equals_Param71, 1));not(equals(Equals_Param70, 2))), (not(equals(Equals_Param70, 7));not(equals(Equals_Param71, 8))), (not(equals(Equals_Param70, 6));not(equals(Equals_Param71, 8))), (not(equals(Equals_Param70, 6));not(equals(Equals_Param71, 7))), (not(equals(Equals_Param70, 5));not(equals(Equals_Param71, 8))), (not(equals(Equals_Param70, 5));not(equals(Equals_Param71, 7))), (not(equals(Equals_Param70, 5));not(equals(Equals_Param71, 6))), (not(equals(Equals_Param70, 3));not(equals(Equals_Param71, 4))), (not(equals(Equals_Param70, 2));not(equals(Equals_Param71, 4))), (not(equals(Equals_Param70, 2));not(equals(Equals_Param71, 3))), (not(equals(Equals_Param70, 1));not(equals(Equals_Param71, 4))), (not(equals(Equals_Param70, 1));not(equals(Equals_Param71, 3))), (not(equals(Equals_Param70, 1));not(equals(Equals_Param71, 2))), neighbor(Equals_Param70, Equals_Param71)),  (equals(Equals_Param72, 3):-((not(equals(Equals_Param72, 5));not(equals(Equals_Param73, 6))), (not(equals(Equals_Param72, 5));not(equals(Equals_Param73, 7))), (not(equals(Equals_Param72, 5));not(equals(Equals_Param73, 8))), (not(equals(Equals_Param72, 6));not(equals(Equals_Param73, 7))), (not(equals(Equals_Param72, 6));not(equals(Equals_Param73, 8))), (not(equals(Equals_Param72, 7));not(equals(Equals_Param73, 8))), (not(equals(Equals_Param73, 4));not(equals(Equals_Param72, 7))), (not(equals(Equals_Param72, 4));not(equals(Equals_Param73, 7)))), (not(equals(Equals_Param72, 2));not(equals(Equals_Param73, 4))), (not(equals(Equals_Param72, 2));not(equals(Equals_Param73, 3))), (not(equals(Equals_Param72, 1));not(equals(Equals_Param73, 4))), (not(equals(Equals_Param72, 1));not(equals(Equals_Param73, 3))), (not(equals(Equals_Param72, 1));not(equals(Equals_Param73, 2))), (not(equals(Equals_Param73, 7));not(equals(Equals_Param72, 8))), (not(equals(Equals_Param73, 6));not(equals(Equals_Param72, 8))), (not(equals(Equals_Param73, 6));not(equals(Equals_Param72, 7))), (not(equals(Equals_Param73, 5));not(equals(Equals_Param72, 8))), (not(equals(Equals_Param73, 5));not(equals(Equals_Param72, 7))), (not(equals(Equals_Param73, 5));not(equals(Equals_Param72, 6))), (not(equals(Equals_Param73, 3));not(equals(Equals_Param72, 4))), (not(equals(Equals_Param73, 2));not(equals(Equals_Param72, 4))), (not(equals(Equals_Param73, 2));not(equals(Equals_Param72, 3))), (not(equals(Equals_Param73, 1));not(equals(Equals_Param72, 4))), (not(equals(Equals_Param73, 1));not(equals(Equals_Param72, 3))), (not(equals(Equals_Param73, 1));not(equals(Equals_Param72, 2))), neighbor(Equals_Param73, Equals_Param72)),  (equals(Equals_Param74, 4):-((not(equals(Equals_Param75, 5));not(equals(Equals_Param74, 6))), (not(equals(Equals_Param75, 5));not(equals(Equals_Param74, 7))), (not(equals(Equals_Param75, 5));not(equals(Equals_Param74, 8))), (not(equals(Equals_Param75, 6));not(equals(Equals_Param74, 7))), (not(equals(Equals_Param75, 6));not(equals(Equals_Param74, 8))), (not(equals(Equals_Param75, 7));not(equals(Equals_Param74, 8))), (not(equals(Equals_Param74, 4));not(equals(Equals_Param75, 7))), (not(equals(Equals_Param75, 4));not(equals(Equals_Param74, 7)))), (not(equals(Equals_Param75, 2));not(equals(Equals_Param74, 4))), (not(equals(Equals_Param75, 2));not(equals(Equals_Param74, 3))), (not(equals(Equals_Param75, 1));not(equals(Equals_Param74, 4))), (not(equals(Equals_Param75, 1));not(equals(Equals_Param74, 3))), (not(equals(Equals_Param75, 1));not(equals(Equals_Param74, 2))), (not(equals(Equals_Param74, 7));not(equals(Equals_Param75, 8))), (not(equals(Equals_Param74, 6));not(equals(Equals_Param75, 8))), (not(equals(Equals_Param74, 6));not(equals(Equals_Param75, 7))), (not(equals(Equals_Param74, 5));not(equals(Equals_Param75, 8))), (not(equals(Equals_Param74, 5));not(equals(Equals_Param75, 7))), (not(equals(Equals_Param74, 5));not(equals(Equals_Param75, 6))), (not(equals(Equals_Param74, 3));not(equals(Equals_Param75, 4))), (not(equals(Equals_Param74, 2));not(equals(Equals_Param75, 4))), (not(equals(Equals_Param74, 2));not(equals(Equals_Param75, 3))), (not(equals(Equals_Param74, 1));not(equals(Equals_Param75, 4))), (not(equals(Equals_Param74, 1));not(equals(Equals_Param75, 3))), (not(equals(Equals_Param74, 1));not(equals(Equals_Param75, 2))), neighbor(Equals_Param74, Equals_Param75)),  (equals(Equals_Param76, 5):-((not(equals(Equals_Param76, 5));not(equals(Equals_Param77, 7))), (not(equals(Equals_Param76, 5));not(equals(Equals_Param77, 8))), (not(equals(Equals_Param76, 6));not(equals(Equals_Param77, 7))), (not(equals(Equals_Param76, 6));not(equals(Equals_Param77, 8))), (not(equals(Equals_Param76, 7));not(equals(Equals_Param77, 8))), (not(equals(Equals_Param77, 4));not(equals(Equals_Param76, 7))), (not(equals(Equals_Param76, 4));not(equals(Equals_Param77, 7)))), (not(equals(Equals_Param76, 3));not(equals(Equals_Param77, 4))), (not(equals(Equals_Param76, 2));not(equals(Equals_Param77, 4))), (not(equals(Equals_Param76, 2));not(equals(Equals_Param77, 3))), (not(equals(Equals_Param76, 1));not(equals(Equals_Param77, 4))), (not(equals(Equals_Param76, 1));not(equals(Equals_Param77, 3))), (not(equals(Equals_Param76, 1));not(equals(Equals_Param77, 2))), (not(equals(Equals_Param77, 7));not(equals(Equals_Param76, 8))), (not(equals(Equals_Param77, 6));not(equals(Equals_Param76, 8))), (not(equals(Equals_Param77, 6));not(equals(Equals_Param76, 7))), (not(equals(Equals_Param77, 5));not(equals(Equals_Param76, 8))), (not(equals(Equals_Param77, 5));not(equals(Equals_Param76, 7))), (not(equals(Equals_Param77, 5));not(equals(Equals_Param76, 6))), (not(equals(Equals_Param77, 3));not(equals(Equals_Param76, 4))), (not(equals(Equals_Param77, 2));not(equals(Equals_Param76, 4))), (not(equals(Equals_Param77, 2));not(equals(Equals_Param76, 3))), (not(equals(Equals_Param77, 1));not(equals(Equals_Param76, 4))), (not(equals(Equals_Param77, 1));not(equals(Equals_Param76, 3))), (not(equals(Equals_Param77, 1));not(equals(Equals_Param76, 2))), neighbor(Equals_Param77, Equals_Param76)),  (equals(Equals_Param78, 6):-((not(equals(Equals_Param79, 5));not(equals(Equals_Param78, 7))), (not(equals(Equals_Param79, 5));not(equals(Equals_Param78, 8))), (not(equals(Equals_Param79, 6));not(equals(Equals_Param78, 7))), (not(equals(Equals_Param79, 6));not(equals(Equals_Param78, 8))), (not(equals(Equals_Param79, 7));not(equals(Equals_Param78, 8))), (not(equals(Equals_Param78, 4));not(equals(Equals_Param79, 7))), (not(equals(Equals_Param79, 4));not(equals(Equals_Param78, 7)))), (not(equals(Equals_Param79, 3));not(equals(Equals_Param78, 4))), (not(equals(Equals_Param79, 2));not(equals(Equals_Param78, 4))), (not(equals(Equals_Param79, 2));not(equals(Equals_Param78, 3))), (not(equals(Equals_Param79, 1));not(equals(Equals_Param78, 4))), (not(equals(Equals_Param79, 1));not(equals(Equals_Param78, 3))), (not(equals(Equals_Param79, 1));not(equals(Equals_Param78, 2))), (not(equals(Equals_Param78, 7));not(equals(Equals_Param79, 8))), (not(equals(Equals_Param78, 6));not(equals(Equals_Param79, 8))), (not(equals(Equals_Param78, 6));not(equals(Equals_Param79, 7))), (not(equals(Equals_Param78, 5));not(equals(Equals_Param79, 8))), (not(equals(Equals_Param78, 5));not(equals(Equals_Param79, 7))), (not(equals(Equals_Param78, 5));not(equals(Equals_Param79, 6))), (not(equals(Equals_Param78, 3));not(equals(Equals_Param79, 4))), (not(equals(Equals_Param78, 2));not(equals(Equals_Param79, 4))), (not(equals(Equals_Param78, 2));not(equals(Equals_Param79, 3))), (not(equals(Equals_Param78, 1));not(equals(Equals_Param79, 4))), (not(equals(Equals_Param78, 1));not(equals(Equals_Param79, 3))), (not(equals(Equals_Param78, 1));not(equals(Equals_Param79, 2))), neighbor(Equals_Param78, Equals_Param79)),  (equals(Equals_Param80, 5):-((not(equals(Equals_Param80, 5));not(equals(Equals_Param81, 8))), (not(equals(Equals_Param80, 6));not(equals(Equals_Param81, 7))), (not(equals(Equals_Param80, 6));not(equals(Equals_Param81, 8))), (not(equals(Equals_Param80, 7));not(equals(Equals_Param81, 8))), (not(equals(Equals_Param81, 4));not(equals(Equals_Param80, 7))), (not(equals(Equals_Param80, 4));not(equals(Equals_Param81, 7)))), (not(equals(Equals_Param80, 5));not(equals(Equals_Param81, 6))), (not(equals(Equals_Param80, 3));not(equals(Equals_Param81, 4))), (not(equals(Equals_Param80, 2));not(equals(Equals_Param81, 4))), (not(equals(Equals_Param80, 2));not(equals(Equals_Param81, 3))), (not(equals(Equals_Param80, 1));not(equals(Equals_Param81, 4))), (not(equals(Equals_Param80, 1));not(equals(Equals_Param81, 3))), (not(equals(Equals_Param80, 1));not(equals(Equals_Param81, 2))), (not(equals(Equals_Param81, 7));not(equals(Equals_Param80, 8))), (not(equals(Equals_Param81, 6));not(equals(Equals_Param80, 8))), (not(equals(Equals_Param81, 6));not(equals(Equals_Param80, 7))), (not(equals(Equals_Param81, 5));not(equals(Equals_Param80, 8))), (not(equals(Equals_Param81, 5));not(equals(Equals_Param80, 7))), (not(equals(Equals_Param81, 5));not(equals(Equals_Param80, 6))), (not(equals(Equals_Param81, 3));not(equals(Equals_Param80, 4))), (not(equals(Equals_Param81, 2));not(equals(Equals_Param80, 4))), (not(equals(Equals_Param81, 2));not(equals(Equals_Param80, 3))), (not(equals(Equals_Param81, 1));not(equals(Equals_Param80, 4))), (not(equals(Equals_Param81, 1));not(equals(Equals_Param80, 3))), (not(equals(Equals_Param81, 1));not(equals(Equals_Param80, 2))), neighbor(Equals_Param81, Equals_Param80)),  (equals(Equals_Param82, 7):-((not(equals(Equals_Param83, 5));not(equals(Equals_Param82, 8))), (not(equals(Equals_Param83, 6));not(equals(Equals_Param82, 7))), (not(equals(Equals_Param83, 6));not(equals(Equals_Param82, 8))), (not(equals(Equals_Param83, 7));not(equals(Equals_Param82, 8))), (not(equals(Equals_Param82, 4));not(equals(Equals_Param83, 7))), (not(equals(Equals_Param83, 4));not(equals(Equals_Param82, 7)))), (not(equals(Equals_Param83, 5));not(equals(Equals_Param82, 6))), (not(equals(Equals_Param83, 3));not(equals(Equals_Param82, 4))), (not(equals(Equals_Param83, 2));not(equals(Equals_Param82, 4))), (not(equals(Equals_Param83, 2));not(equals(Equals_Param82, 3))), (not(equals(Equals_Param83, 1));not(equals(Equals_Param82, 4))), (not(equals(Equals_Param83, 1));not(equals(Equals_Param82, 3))), (not(equals(Equals_Param83, 1));not(equals(Equals_Param82, 2))), (not(equals(Equals_Param82, 7));not(equals(Equals_Param83, 8))), (not(equals(Equals_Param82, 6));not(equals(Equals_Param83, 8))), (not(equals(Equals_Param82, 6));not(equals(Equals_Param83, 7))), (not(equals(Equals_Param82, 5));not(equals(Equals_Param83, 8))), (not(equals(Equals_Param82, 5));not(equals(Equals_Param83, 7))), (not(equals(Equals_Param82, 5));not(equals(Equals_Param83, 6))), (not(equals(Equals_Param82, 3));not(equals(Equals_Param83, 4))), (not(equals(Equals_Param82, 2));not(equals(Equals_Param83, 4))), (not(equals(Equals_Param82, 2));not(equals(Equals_Param83, 3))), (not(equals(Equals_Param82, 1));not(equals(Equals_Param83, 4))), (not(equals(Equals_Param82, 1));not(equals(Equals_Param83, 3))), (not(equals(Equals_Param82, 1));not(equals(Equals_Param83, 2))), neighbor(Equals_Param82, Equals_Param83)),  (equals(Equals_Param84, 5):-((not(equals(Equals_Param84, 6));not(equals(Equals_Param85, 7))), (not(equals(Equals_Param84, 6));not(equals(Equals_Param85, 8))), (not(equals(Equals_Param84, 7));not(equals(Equals_Param85, 8))), (not(equals(Equals_Param85, 4));not(equals(Equals_Param84, 7))), (not(equals(Equals_Param84, 4));not(equals(Equals_Param85, 7)))), (not(equals(Equals_Param84, 5));not(equals(Equals_Param85, 7))), (not(equals(Equals_Param84, 5));not(equals(Equals_Param85, 6))), (not(equals(Equals_Param84, 3));not(equals(Equals_Param85, 4))), (not(equals(Equals_Param84, 2));not(equals(Equals_Param85, 4))), (not(equals(Equals_Param84, 2));not(equals(Equals_Param85, 3))), (not(equals(Equals_Param84, 1));not(equals(Equals_Param85, 4))), (not(equals(Equals_Param84, 1));not(equals(Equals_Param85, 3))), (not(equals(Equals_Param84, 1));not(equals(Equals_Param85, 2))), (not(equals(Equals_Param85, 7));not(equals(Equals_Param84, 8))), (not(equals(Equals_Param85, 6));not(equals(Equals_Param84, 8))), (not(equals(Equals_Param85, 6));not(equals(Equals_Param84, 7))), (not(equals(Equals_Param85, 5));not(equals(Equals_Param84, 8))), (not(equals(Equals_Param85, 5));not(equals(Equals_Param84, 7))), (not(equals(Equals_Param85, 5));not(equals(Equals_Param84, 6))), (not(equals(Equals_Param85, 3));not(equals(Equals_Param84, 4))), (not(equals(Equals_Param85, 2));not(equals(Equals_Param84, 4))), (not(equals(Equals_Param85, 2));not(equals(Equals_Param84, 3))), (not(equals(Equals_Param85, 1));not(equals(Equals_Param84, 4))), (not(equals(Equals_Param85, 1));not(equals(Equals_Param84, 3))), (not(equals(Equals_Param85, 1));not(equals(Equals_Param84, 2))), neighbor(Equals_Param85, Equals_Param84)),  (equals(Equals_Param86, 8):-((not(equals(Equals_Param87, 6));not(equals(Equals_Param86, 7))), (not(equals(Equals_Param87, 6));not(equals(Equals_Param86, 8))), (not(equals(Equals_Param87, 7));not(equals(Equals_Param86, 8))), (not(equals(Equals_Param86, 4));not(equals(Equals_Param87, 7))), (not(equals(Equals_Param87, 4));not(equals(Equals_Param86, 7)))), (not(equals(Equals_Param87, 5));not(equals(Equals_Param86, 7))), (not(equals(Equals_Param87, 5));not(equals(Equals_Param86, 6))), (not(equals(Equals_Param87, 3));not(equals(Equals_Param86, 4))), (not(equals(Equals_Param87, 2));not(equals(Equals_Param86, 4))), (not(equals(Equals_Param87, 2));not(equals(Equals_Param86, 3))), (not(equals(Equals_Param87, 1));not(equals(Equals_Param86, 4))), (not(equals(Equals_Param87, 1));not(equals(Equals_Param86, 3))), (not(equals(Equals_Param87, 1));not(equals(Equals_Param86, 2))), (not(equals(Equals_Param86, 7));not(equals(Equals_Param87, 8))), (not(equals(Equals_Param86, 6));not(equals(Equals_Param87, 8))), (not(equals(Equals_Param86, 6));not(equals(Equals_Param87, 7))), (not(equals(Equals_Param86, 5));not(equals(Equals_Param87, 8))), (not(equals(Equals_Param86, 5));not(equals(Equals_Param87, 7))), (not(equals(Equals_Param86, 5));not(equals(Equals_Param87, 6))), (not(equals(Equals_Param86, 3));not(equals(Equals_Param87, 4))), (not(equals(Equals_Param86, 2));not(equals(Equals_Param87, 4))), (not(equals(Equals_Param86, 2));not(equals(Equals_Param87, 3))), (not(equals(Equals_Param86, 1));not(equals(Equals_Param87, 4))), (not(equals(Equals_Param86, 1));not(equals(Equals_Param87, 3))), (not(equals(Equals_Param86, 1));not(equals(Equals_Param87, 2))), neighbor(Equals_Param86, Equals_Param87)),  (equals(Equals_Param88, 6):-((not(equals(Equals_Param88, 6));not(equals(Equals_Param89, 8))), (not(equals(Equals_Param88, 7));not(equals(Equals_Param89, 8))), (not(equals(Equals_Param89, 4));not(equals(Equals_Param88, 7))), (not(equals(Equals_Param88, 4));not(equals(Equals_Param89, 7)))), (not(equals(Equals_Param88, 5));not(equals(Equals_Param89, 8))), (not(equals(Equals_Param88, 5));not(equals(Equals_Param89, 7))), (not(equals(Equals_Param88, 5));not(equals(Equals_Param89, 6))), (not(equals(Equals_Param88, 3));not(equals(Equals_Param89, 4))), (not(equals(Equals_Param88, 2));not(equals(Equals_Param89, 4))), (not(equals(Equals_Param88, 2));not(equals(Equals_Param89, 3))), (not(equals(Equals_Param88, 1));not(equals(Equals_Param89, 4))), (not(equals(Equals_Param88, 1));not(equals(Equals_Param89, 3))), (not(equals(Equals_Param88, 1));not(equals(Equals_Param89, 2))), (not(equals(Equals_Param89, 7));not(equals(Equals_Param88, 8))), (not(equals(Equals_Param89, 6));not(equals(Equals_Param88, 8))), (not(equals(Equals_Param89, 6));not(equals(Equals_Param88, 7))), (not(equals(Equals_Param89, 5));not(equals(Equals_Param88, 8))), (not(equals(Equals_Param89, 5));not(equals(Equals_Param88, 7))), (not(equals(Equals_Param89, 5));not(equals(Equals_Param88, 6))), (not(equals(Equals_Param89, 3));not(equals(Equals_Param88, 4))), (not(equals(Equals_Param89, 2));not(equals(Equals_Param88, 4))), (not(equals(Equals_Param89, 2));not(equals(Equals_Param88, 3))), (not(equals(Equals_Param89, 1));not(equals(Equals_Param88, 4))), (not(equals(Equals_Param89, 1));not(equals(Equals_Param88, 3))), (not(equals(Equals_Param89, 1));not(equals(Equals_Param88, 2))), neighbor(Equals_Param89, Equals_Param88)),  (equals(Equals_Param90, 7):-((not(equals(Equals_Param91, 6));not(equals(Equals_Param90, 8))), (not(equals(Equals_Param91, 7));not(equals(Equals_Param90, 8))), (not(equals(Equals_Param90, 4));not(equals(Equals_Param91, 7))), (not(equals(Equals_Param91, 4));not(equals(Equals_Param90, 7)))), (not(equals(Equals_Param91, 5));not(equals(Equals_Param90, 8))), (not(equals(Equals_Param91, 5));not(equals(Equals_Param90, 7))), (not(equals(Equals_Param91, 5));not(equals(Equals_Param90, 6))), (not(equals(Equals_Param91, 3));not(equals(Equals_Param90, 4))), (not(equals(Equals_Param91, 2));not(equals(Equals_Param90, 4))), (not(equals(Equals_Param91, 2));not(equals(Equals_Param90, 3))), (not(equals(Equals_Param91, 1));not(equals(Equals_Param90, 4))), (not(equals(Equals_Param91, 1));not(equals(Equals_Param90, 3))), (not(equals(Equals_Param91, 1));not(equals(Equals_Param90, 2))), (not(equals(Equals_Param90, 7));not(equals(Equals_Param91, 8))), (not(equals(Equals_Param90, 6));not(equals(Equals_Param91, 8))), (not(equals(Equals_Param90, 6));not(equals(Equals_Param91, 7))), (not(equals(Equals_Param90, 5));not(equals(Equals_Param91, 8))), (not(equals(Equals_Param90, 5));not(equals(Equals_Param91, 7))), (not(equals(Equals_Param90, 5));not(equals(Equals_Param91, 6))), (not(equals(Equals_Param90, 3));not(equals(Equals_Param91, 4))), (not(equals(Equals_Param90, 2));not(equals(Equals_Param91, 4))), (not(equals(Equals_Param90, 2));not(equals(Equals_Param91, 3))), (not(equals(Equals_Param90, 1));not(equals(Equals_Param91, 4))), (not(equals(Equals_Param90, 1));not(equals(Equals_Param91, 3))), (not(equals(Equals_Param90, 1));not(equals(Equals_Param91, 2))), neighbor(Equals_Param90, Equals_Param91)),  (equals(Equals_Param92, 6):-((not(equals(Equals_Param92, 7));not(equals(Equals_Param93, 8))), (not(equals(Equals_Param93, 4));not(equals(Equals_Param92, 7))), (not(equals(Equals_Param92, 4));not(equals(Equals_Param93, 7)))), (not(equals(Equals_Param92, 6));not(equals(Equals_Param93, 7))), (not(equals(Equals_Param92, 5));not(equals(Equals_Param93, 8))), (not(equals(Equals_Param92, 5));not(equals(Equals_Param93, 7))), (not(equals(Equals_Param92, 5));not(equals(Equals_Param93, 6))), (not(equals(Equals_Param92, 3));not(equals(Equals_Param93, 4))), (not(equals(Equals_Param92, 2));not(equals(Equals_Param93, 4))), (not(equals(Equals_Param92, 2));not(equals(Equals_Param93, 3))), (not(equals(Equals_Param92, 1));not(equals(Equals_Param93, 4))), (not(equals(Equals_Param92, 1));not(equals(Equals_Param93, 3))), (not(equals(Equals_Param92, 1));not(equals(Equals_Param93, 2))), (not(equals(Equals_Param93, 7));not(equals(Equals_Param92, 8))), (not(equals(Equals_Param93, 6));not(equals(Equals_Param92, 8))), (not(equals(Equals_Param93, 6));not(equals(Equals_Param92, 7))), (not(equals(Equals_Param93, 5));not(equals(Equals_Param92, 8))), (not(equals(Equals_Param93, 5));not(equals(Equals_Param92, 7))), (not(equals(Equals_Param93, 5));not(equals(Equals_Param92, 6))), (not(equals(Equals_Param93, 3));not(equals(Equals_Param92, 4))), (not(equals(Equals_Param93, 2));not(equals(Equals_Param92, 4))), (not(equals(Equals_Param93, 2));not(equals(Equals_Param92, 3))), (not(equals(Equals_Param93, 1));not(equals(Equals_Param92, 4))), (not(equals(Equals_Param93, 1));not(equals(Equals_Param92, 3))), (not(equals(Equals_Param93, 1));not(equals(Equals_Param92, 2))), neighbor(Equals_Param93, Equals_Param92)),  (equals(Equals_Param94, 8):-((not(equals(Equals_Param95, 7));not(equals(Equals_Param94, 8))), (not(equals(Equals_Param94, 4));not(equals(Equals_Param95, 7))), (not(equals(Equals_Param95, 4));not(equals(Equals_Param94, 7)))), (not(equals(Equals_Param95, 6));not(equals(Equals_Param94, 7))), (not(equals(Equals_Param95, 5));not(equals(Equals_Param94, 8))), (not(equals(Equals_Param95, 5));not(equals(Equals_Param94, 7))), (not(equals(Equals_Param95, 5));not(equals(Equals_Param94, 6))), (not(equals(Equals_Param95, 3));not(equals(Equals_Param94, 4))), (not(equals(Equals_Param95, 2));not(equals(Equals_Param94, 4))), (not(equals(Equals_Param95, 2));not(equals(Equals_Param94, 3))), (not(equals(Equals_Param95, 1));not(equals(Equals_Param94, 4))), (not(equals(Equals_Param95, 1));not(equals(Equals_Param94, 3))), (not(equals(Equals_Param95, 1));not(equals(Equals_Param94, 2))), (not(equals(Equals_Param94, 7));not(equals(Equals_Param95, 8))), (not(equals(Equals_Param94, 6));not(equals(Equals_Param95, 8))), (not(equals(Equals_Param94, 6));not(equals(Equals_Param95, 7))), (not(equals(Equals_Param94, 5));not(equals(Equals_Param95, 8))), (not(equals(Equals_Param94, 5));not(equals(Equals_Param95, 7))), (not(equals(Equals_Param94, 5));not(equals(Equals_Param95, 6))), (not(equals(Equals_Param94, 3));not(equals(Equals_Param95, 4))), (not(equals(Equals_Param94, 2));not(equals(Equals_Param95, 4))), (not(equals(Equals_Param94, 2));not(equals(Equals_Param95, 3))), (not(equals(Equals_Param94, 1));not(equals(Equals_Param95, 4))), (not(equals(Equals_Param94, 1));not(equals(Equals_Param95, 3))), (not(equals(Equals_Param94, 1));not(equals(Equals_Param95, 2))), neighbor(Equals_Param94, Equals_Param95)),  (equals(Equals_Param96, 7):-((not(equals(Equals_Param97, 4));not(equals(Equals_Param96, 7))), (not(equals(Equals_Param96, 4));not(equals(Equals_Param97, 7)))), (not(equals(Equals_Param96, 6));not(equals(Equals_Param97, 8))), (not(equals(Equals_Param96, 6));not(equals(Equals_Param97, 7))), (not(equals(Equals_Param96, 5));not(equals(Equals_Param97, 8))), (not(equals(Equals_Param96, 5));not(equals(Equals_Param97, 7))), (not(equals(Equals_Param96, 5));not(equals(Equals_Param97, 6))), (not(equals(Equals_Param96, 3));not(equals(Equals_Param97, 4))), (not(equals(Equals_Param96, 2));not(equals(Equals_Param97, 4))), (not(equals(Equals_Param96, 2));not(equals(Equals_Param97, 3))), (not(equals(Equals_Param96, 1));not(equals(Equals_Param97, 4))), (not(equals(Equals_Param96, 1));not(equals(Equals_Param97, 3))), (not(equals(Equals_Param96, 1));not(equals(Equals_Param97, 2))), (not(equals(Equals_Param97, 7));not(equals(Equals_Param96, 8))), (not(equals(Equals_Param97, 6));not(equals(Equals_Param96, 8))), (not(equals(Equals_Param97, 6));not(equals(Equals_Param96, 7))), (not(equals(Equals_Param97, 5));not(equals(Equals_Param96, 8))), (not(equals(Equals_Param97, 5));not(equals(Equals_Param96, 7))), (not(equals(Equals_Param97, 5));not(equals(Equals_Param96, 6))), (not(equals(Equals_Param97, 3));not(equals(Equals_Param96, 4))), (not(equals(Equals_Param97, 2));not(equals(Equals_Param96, 4))), (not(equals(Equals_Param97, 2));not(equals(Equals_Param96, 3))), (not(equals(Equals_Param97, 1));not(equals(Equals_Param96, 4))), (not(equals(Equals_Param97, 1));not(equals(Equals_Param96, 3))), (not(equals(Equals_Param97, 1));not(equals(Equals_Param96, 2))), neighbor(Equals_Param97, Equals_Param96)),  (equals(Equals_Param98, 8):-((not(equals(Equals_Param98, 4));not(equals(Equals_Param99, 7))), (not(equals(Equals_Param99, 4));not(equals(Equals_Param98, 7)))), (not(equals(Equals_Param99, 6));not(equals(Equals_Param98, 8))), (not(equals(Equals_Param99, 6));not(equals(Equals_Param98, 7))), (not(equals(Equals_Param99, 5));not(equals(Equals_Param98, 8))), (not(equals(Equals_Param99, 5));not(equals(Equals_Param98, 7))), (not(equals(Equals_Param99, 5));not(equals(Equals_Param98, 6))), (not(equals(Equals_Param99, 3));not(equals(Equals_Param98, 4))), (not(equals(Equals_Param99, 2));not(equals(Equals_Param98, 4))), (not(equals(Equals_Param99, 2));not(equals(Equals_Param98, 3))), (not(equals(Equals_Param99, 1));not(equals(Equals_Param98, 4))), (not(equals(Equals_Param99, 1));not(equals(Equals_Param98, 3))), (not(equals(Equals_Param99, 1));not(equals(Equals_Param98, 2))), (not(equals(Equals_Param98, 7));not(equals(Equals_Param99, 8))), (not(equals(Equals_Param98, 6));not(equals(Equals_Param99, 8))), (not(equals(Equals_Param98, 6));not(equals(Equals_Param99, 7))), (not(equals(Equals_Param98, 5));not(equals(Equals_Param99, 8))), (not(equals(Equals_Param98, 5));not(equals(Equals_Param99, 7))), (not(equals(Equals_Param98, 5));not(equals(Equals_Param99, 6))), (not(equals(Equals_Param98, 3));not(equals(Equals_Param99, 4))), (not(equals(Equals_Param98, 2));not(equals(Equals_Param99, 4))), (not(equals(Equals_Param98, 2));not(equals(Equals_Param99, 3))), (not(equals(Equals_Param98, 1));not(equals(Equals_Param99, 4))), (not(equals(Equals_Param98, 1));not(equals(Equals_Param99, 3))), (not(equals(Equals_Param98, 1));not(equals(Equals_Param99, 2))), neighbor(Equals_Param98, Equals_Param99)),  (equals(Equals_Param100, 4):-(not(equals(Equals_Param101, 4));not(equals(Equals_Param100, 7))), (not(equals(Equals_Param101, 7));not(equals(Equals_Param100, 8))), (not(equals(Equals_Param101, 6));not(equals(Equals_Param100, 8))), (not(equals(Equals_Param101, 6));not(equals(Equals_Param100, 7))), (not(equals(Equals_Param101, 5));not(equals(Equals_Param100, 8))), (not(equals(Equals_Param101, 5));not(equals(Equals_Param100, 7))), (not(equals(Equals_Param101, 5));not(equals(Equals_Param100, 6))), (not(equals(Equals_Param101, 3));not(equals(Equals_Param100, 4))), (not(equals(Equals_Param101, 2));not(equals(Equals_Param100, 4))), (not(equals(Equals_Param101, 2));not(equals(Equals_Param100, 3))), (not(equals(Equals_Param101, 1));not(equals(Equals_Param100, 4))), (not(equals(Equals_Param101, 1));not(equals(Equals_Param100, 3))), (not(equals(Equals_Param101, 1));not(equals(Equals_Param100, 2))), (not(equals(Equals_Param100, 7));not(equals(Equals_Param101, 8))), (not(equals(Equals_Param100, 6));not(equals(Equals_Param101, 8))), (not(equals(Equals_Param100, 6));not(equals(Equals_Param101, 7))), (not(equals(Equals_Param100, 5));not(equals(Equals_Param101, 8))), (not(equals(Equals_Param100, 5));not(equals(Equals_Param101, 7))), (not(equals(Equals_Param100, 5));not(equals(Equals_Param101, 6))), (not(equals(Equals_Param100, 3));not(equals(Equals_Param101, 4))), (not(equals(Equals_Param100, 2));not(equals(Equals_Param101, 4))), (not(equals(Equals_Param100, 2));not(equals(Equals_Param101, 3))), (not(equals(Equals_Param100, 1));not(equals(Equals_Param101, 4))), (not(equals(Equals_Param100, 1));not(equals(Equals_Param101, 3))), (not(equals(Equals_Param100, 1));not(equals(Equals_Param101, 2))), neighbor(Equals_Param100, Equals_Param101)),  (equals(Equals_Param102, 7):-(not(equals(Equals_Param102, 4));not(equals(Equals_Param103, 7))), (not(equals(Equals_Param102, 7));not(equals(Equals_Param103, 8))), (not(equals(Equals_Param102, 6));not(equals(Equals_Param103, 8))), (not(equals(Equals_Param102, 6));not(equals(Equals_Param103, 7))), (not(equals(Equals_Param102, 5));not(equals(Equals_Param103, 8))), (not(equals(Equals_Param102, 5));not(equals(Equals_Param103, 7))), (not(equals(Equals_Param102, 5));not(equals(Equals_Param103, 6))), (not(equals(Equals_Param102, 3));not(equals(Equals_Param103, 4))), (not(equals(Equals_Param102, 2));not(equals(Equals_Param103, 4))), (not(equals(Equals_Param102, 2));not(equals(Equals_Param103, 3))), (not(equals(Equals_Param102, 1));not(equals(Equals_Param103, 4))), (not(equals(Equals_Param102, 1));not(equals(Equals_Param103, 3))), (not(equals(Equals_Param102, 1));not(equals(Equals_Param103, 2))), (not(equals(Equals_Param103, 7));not(equals(Equals_Param102, 8))), (not(equals(Equals_Param103, 6));not(equals(Equals_Param102, 8))), (not(equals(Equals_Param103, 6));not(equals(Equals_Param102, 7))), (not(equals(Equals_Param103, 5));not(equals(Equals_Param102, 8))), (not(equals(Equals_Param103, 5));not(equals(Equals_Param102, 7))), (not(equals(Equals_Param103, 5));not(equals(Equals_Param102, 6))), (not(equals(Equals_Param103, 3));not(equals(Equals_Param102, 4))), (not(equals(Equals_Param103, 2));not(equals(Equals_Param102, 4))), (not(equals(Equals_Param103, 2));not(equals(Equals_Param102, 3))), (not(equals(Equals_Param103, 1));not(equals(Equals_Param102, 4))), (not(equals(Equals_Param103, 1));not(equals(Equals_Param102, 3))), (not(equals(Equals_Param103, 1));not(equals(Equals_Param102, 2))), neighbor(Equals_Param103, Equals_Param102)),  (equals(Equals_Param104, 4):-(not(equals(Equals_Param105, 4));not(equals(Equals_Param104, 7))), (not(equals(Equals_Param104, 7));not(equals(Equals_Param105, 8))), (not(equals(Equals_Param104, 6));not(equals(Equals_Param105, 8))), (not(equals(Equals_Param104, 6));not(equals(Equals_Param105, 7))), (not(equals(Equals_Param104, 5));not(equals(Equals_Param105, 8))), (not(equals(Equals_Param104, 5));not(equals(Equals_Param105, 7))), (not(equals(Equals_Param104, 5));not(equals(Equals_Param105, 6))), (not(equals(Equals_Param104, 3));not(equals(Equals_Param105, 4))), (not(equals(Equals_Param104, 2));not(equals(Equals_Param105, 4))), (not(equals(Equals_Param104, 2));not(equals(Equals_Param105, 3))), (not(equals(Equals_Param104, 1));not(equals(Equals_Param105, 4))), (not(equals(Equals_Param104, 1));not(equals(Equals_Param105, 3))), (not(equals(Equals_Param104, 1));not(equals(Equals_Param105, 2))), (not(equals(Equals_Param105, 7));not(equals(Equals_Param104, 8))), (not(equals(Equals_Param105, 6));not(equals(Equals_Param104, 8))), (not(equals(Equals_Param105, 6));not(equals(Equals_Param104, 7))), (not(equals(Equals_Param105, 5));not(equals(Equals_Param104, 8))), (not(equals(Equals_Param105, 5));not(equals(Equals_Param104, 7))), (not(equals(Equals_Param105, 5));not(equals(Equals_Param104, 6))), (not(equals(Equals_Param105, 3));not(equals(Equals_Param104, 4))), (not(equals(Equals_Param105, 2));not(equals(Equals_Param104, 4))), (not(equals(Equals_Param105, 2));not(equals(Equals_Param104, 3))), (not(equals(Equals_Param105, 1));not(equals(Equals_Param104, 4))), (not(equals(Equals_Param105, 1));not(equals(Equals_Param104, 3))), (not(equals(Equals_Param105, 1));not(equals(Equals_Param104, 2))), neighbor(Equals_Param105, Equals_Param104)),  (equals(Equals_Param106, 7):-(not(equals(Equals_Param106, 4));not(equals(Equals_Param107, 7))), (not(equals(Equals_Param107, 7));not(equals(Equals_Param106, 8))), (not(equals(Equals_Param107, 6));not(equals(Equals_Param106, 8))), (not(equals(Equals_Param107, 6));not(equals(Equals_Param106, 7))), (not(equals(Equals_Param107, 5));not(equals(Equals_Param106, 8))), (not(equals(Equals_Param107, 5));not(equals(Equals_Param106, 7))), (not(equals(Equals_Param107, 5));not(equals(Equals_Param106, 6))), (not(equals(Equals_Param107, 3));not(equals(Equals_Param106, 4))), (not(equals(Equals_Param107, 2));not(equals(Equals_Param106, 4))), (not(equals(Equals_Param107, 2));not(equals(Equals_Param106, 3))), (not(equals(Equals_Param107, 1));not(equals(Equals_Param106, 4))), (not(equals(Equals_Param107, 1));not(equals(Equals_Param106, 3))), (not(equals(Equals_Param107, 1));not(equals(Equals_Param106, 2))), (not(equals(Equals_Param106, 7));not(equals(Equals_Param107, 8))), (not(equals(Equals_Param106, 6));not(equals(Equals_Param107, 8))), (not(equals(Equals_Param106, 6));not(equals(Equals_Param107, 7))), (not(equals(Equals_Param106, 5));not(equals(Equals_Param107, 8))), (not(equals(Equals_Param106, 5));not(equals(Equals_Param107, 7))), (not(equals(Equals_Param106, 5));not(equals(Equals_Param107, 6))), (not(equals(Equals_Param106, 3));not(equals(Equals_Param107, 4))), (not(equals(Equals_Param106, 2));not(equals(Equals_Param107, 4))), (not(equals(Equals_Param106, 2));not(equals(Equals_Param107, 3))), (not(equals(Equals_Param106, 1));not(equals(Equals_Param107, 4))), (not(equals(Equals_Param106, 1));not(equals(Equals_Param107, 3))), (not(equals(Equals_Param106, 1));not(equals(Equals_Param107, 2))), neighbor(Equals_Param106, Equals_Param107))], 53==53).
28837
28838
28839% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8731
28840% Side1(GateAO)=4.
28841side1(gateAO,4).
28842
28843
28844% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8732
28845% Side2(GateAO)=7.
28846side2(gateAO,7).
28847
28848
28849% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8734
28850%; End of file.
28851%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
28852%; FILE: examples/AkmanEtAl2004/ZooTest4.1.e
28853%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
28854%;
28855%; Copyright (c) 2005 IBM Corporation and others.
28856%; All rights reserved. This program and the accompanying materials
28857%; are made available under the terms of the Common Public License v1.0
28858%; which accompanies this distribution, and is available at
28859%; http://www.eclipse.org/legal/cpl-v10.html
28860%;
28861%; Contributors:
28862%; IBM - Initial implementation
28863%;
28864%; @article{Akman:2004,
28865%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
28866%;   year = "2004",
28867%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
28868%;   journal = "Artificial Intelligence",
28869%;   volume = "153",
28870%;   pages = "105--140",
28871%; }
28872%;
28873
28874% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8761
28875% option encoding 3
28876% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8762
28877:- set_ec_option(encoding, 3).28878
28879% load foundations/Root.e
28880
28881% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8764
28882% load foundations/EC.e
28883
28884% load examples/AkmanEtAl2004/ZooWorld.e
28885
28886% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8767
28887% human Homer
28888% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8768
28889==> t(human,homer).
28890
28891% elephant Jumbo
28892% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8769
28893==> t(elephant,jumbo).
28894
28895
28896% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8770
28897% Species(Homer)=HumanSpecies.
28898species(homer,humanSpecies).
28899
28900
28901% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8771
28902% Adult(Homer).
28903adult(homer).
28904
28905
28906% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8772
28907% Species(Jumbo)=ElephantSpecies.
28908species(jumbo,elephantSpecies).
28909
28910
28911% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8773
28912% Adult(Jumbo).
28913adult(jumbo).
28914
28915
28916% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8775
28917% !HoldsAt(Opened(GateAO),0).
28918 %  not(initially(opened(gateAO))).
28919axiom(not(initially(opened(gateAO))),
28920    []).
28921% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8776
28922% {position} 
28923
28924
28925% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8776
28926% HoldsAt(Pos(Homer,position),0) & Outside=Loc(position).
28927
28928 /*   exists([Position],
28929              (holds_at(pos(homer, Position), 0), outside=loc(Position))).
28930 */
28931
28932 /*  not(some(Some_Param, '$kolem_Fn_416')) :-
28933       (   not(holds_at(pos(homer, Some_Param), 0))
28934       ;   not(equals(outside, loc(Some_Param)))
28935       ).
28936 */
28937axiom(not(some(Some_Param, '$kolem_Fn_416')),
28938    [not(holds_at(pos(homer, Some_Param), t))]).
28939axiom(not(some(Some_Param, '$kolem_Fn_416')),
28940    [not(equals(outside, loc(Some_Param)))]).
28941
28942 /*  holds_at(pos(homer, Some_Param3), 0) :-
28943       some(Some_Param3, '$kolem_Fn_416').
28944 */
28945axiom(holds_at(pos(homer, Some_Param3), t),
28946    [some(Some_Param3, '$kolem_Fn_416')]).
28947
28948 /*  equals(outside, loc(Some_Param4)) :-
28949       some(Some_Param4, '$kolem_Fn_416').
28950 */
28951axiom(equals(outside, loc(Some_Param4)),
28952    [some(Some_Param4, '$kolem_Fn_416')]).
28953% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8777
28954% {position} 
28955
28956
28957% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8777
28958% HoldsAt(Pos(Jumbo,position),0) & CageA=Loc(position).
28959
28960 /*   exists([Position],
28961              (holds_at(pos(jumbo, Position), 0), cageA=loc(Position))).
28962 */
28963
28964 /*  not(some(Some_Param, '$kolem_Fn_417')) :-
28965       (   not(holds_at(pos(jumbo, Some_Param), 0))
28966       ;   not(equals(cageA, loc(Some_Param)))
28967       ).
28968 */
28969axiom(not(some(Some_Param, '$kolem_Fn_417')),
28970    [not(holds_at(pos(jumbo, Some_Param), t))]).
28971axiom(not(some(Some_Param, '$kolem_Fn_417')),
28972    [not(equals(cageA, loc(Some_Param)))]).
28973
28974 /*  holds_at(pos(jumbo, Some_Param3), 0) :-
28975       some(Some_Param3, '$kolem_Fn_417').
28976 */
28977axiom(holds_at(pos(jumbo, Some_Param3), t),
28978    [some(Some_Param3, '$kolem_Fn_417')]).
28979
28980 /*  equals(cageA, loc(Some_Param4)) :-
28981       some(Some_Param4, '$kolem_Fn_417').
28982 */
28983axiom(equals(cageA, loc(Some_Param4)),
28984    [some(Some_Param4, '$kolem_Fn_417')]).
28985% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8779
28986% {position} 
28987
28988
28989% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8779
28990% HoldsAt(Pos(Homer,position),4) & CageA=Loc(position).
28991
28992 /*   exists([Position],
28993              (holds_at(pos(homer, Position), 4), cageA=loc(Position))).
28994 */
28995
28996 /*  not(some(Some_Param, '$kolem_Fn_418')) :-
28997       (   not(holds_at(pos(homer, Some_Param), 4))
28998       ;   not(equals(cageA, loc(Some_Param)))
28999       ).
29000 */
29001axiom(not(some(Some_Param, '$kolem_Fn_418')),
29002    [not(holds_at(pos(homer, Some_Param), t4)), b(t, t4), ignore(t+4=t4)]).
29003axiom(not(some(Some_Param, '$kolem_Fn_418')),
29004    [not(equals(cageA, loc(Some_Param)))]).
29005
29006 /*  holds_at(pos(homer, Some_Param3), 4) :-
29007       some(Some_Param3, '$kolem_Fn_418').
29008 */
29009axiom(holds_at(pos(homer, Some_Param3), t4),
29010    [some(Some_Param3, '$kolem_Fn_418'), b(t, t4), ignore(t+4=t4)]).
29011
29012 /*  equals(cageA, loc(Some_Param4)) :-
29013       some(Some_Param4, '$kolem_Fn_418').
29014 */
29015axiom(equals(cageA, loc(Some_Param4)),
29016    [some(Some_Param4, '$kolem_Fn_418')]).
29017% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8780
29018% {position} 
29019
29020
29021% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8780
29022% HoldsAt(Pos(Jumbo,position),4) & Outside=Loc(position).
29023
29024 /*   exists([Position],
29025              (holds_at(pos(jumbo, Position), 4), outside=loc(Position))).
29026 */
29027
29028 /*  not(some(Some_Param, '$kolem_Fn_419')) :-
29029       (   not(holds_at(pos(jumbo, Some_Param), 4))
29030       ;   not(equals(outside, loc(Some_Param)))
29031       ).
29032 */
29033axiom(not(some(Some_Param, '$kolem_Fn_419')),
29034    [not(holds_at(pos(jumbo, Some_Param), t4)), b(t, t4), ignore(t+4=t4)]).
29035axiom(not(some(Some_Param, '$kolem_Fn_419')),
29036    [not(equals(outside, loc(Some_Param)))]).
29037
29038 /*  holds_at(pos(jumbo, Some_Param3), 4) :-
29039       some(Some_Param3, '$kolem_Fn_419').
29040 */
29041axiom(holds_at(pos(jumbo, Some_Param3), t4),
29042    [some(Some_Param3, '$kolem_Fn_419'), b(t, t4), ignore(t+4=t4)]).
29043
29044 /*  equals(outside, loc(Some_Param4)) :-
29045       some(Some_Param4, '$kolem_Fn_419').
29046 */
29047axiom(equals(outside, loc(Some_Param4)),
29048    [some(Some_Param4, '$kolem_Fn_419')]).
29049
29050
29051% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8782
29052% [human]
29053 % HoldsAt(PosDeterminingFluent(human,1),4).
29054holds_at(posDeterminingFluent(Human,1),4).
29055
29056
29057% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8783
29058% [event,animal]
29059 % !HoldsAt(DoneBy(event,animal),4).
29060 %  not(holds_at(doneBy(Event,Animal),4)).
29061axiom(not(holds_at(doneBy(DoneBy_Param, DoneBy_Ret), t4)),
29062    [b(t, t4), ignore(t+4=t4)]).
29063
29064
29065% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8785
29066%; ccalc.2.0b.8.3 single model
29067%;HoldsAt(Pos(Homer,7),0).
29068%;HoldsAt(Pos(Jumbo,2),0).
29069%;Happens(Move(Jumbo,4),0).
29070%;Happens(Open(Homer,GateAO),0).
29071%;Happens(Mount(Homer,Jumbo),1).
29072%;Happens(ThrowOff(Jumbo,Homer),2).
29073%;HoldsAt(PosDeterminingFluent(Homer,1),2).
29074%;Happens(Move(Jumbo,7),3).
29075%;Happens(Mount(Homer,Jumbo),3).
29076
29077% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8796
29078% range time 0 4
29079% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8797
29080==> range(time,0,4).
29081
29082% range position 1 8
29083% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8798
29084==> range(position,1,8).
29085
29086% range offset 0 0
29087% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8799
29088==> range(offset,0,0).
29089%; End of file.
29090%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
29091%; FILE: examples/AkmanEtAl2004/ZooTest2.e
29092%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
29093%;
29094%; Copyright (c) 2005 IBM Corporation and others.
29095%; All rights reserved. This program and the accompanying materials
29096%; are made available under the terms of the Common Public License v1.0
29097%; which accompanies this distribution, and is available at
29098%; http://www.eclipse.org/legal/cpl-v10.html
29099%;
29100%; Contributors:
29101%; IBM - Initial implementation
29102%;
29103%; @article{Akman:2004,
29104%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
29105%;   year = "2004",
29106%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
29107%;   journal = "Artificial Intelligence",
29108%;   volume = "153",
29109%;   pages = "105--140",
29110%; }
29111%;
29112
29113% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8827
29114% option encoding 3
29115% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8828
29116:- set_ec_option(encoding, 3).29117
29118% load foundations/Root.e
29119
29120% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8830
29121% load foundations/EC.e
29122
29123% load examples/AkmanEtAl2004/ZooWorld.e
29124
29125% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8833
29126% human Homer
29127% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8834
29128==> t(human,homer).
29129
29130
29131% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8835
29132% Species(Homer)=HumanSpecies.
29133species(homer,humanSpecies).
29134
29135
29136% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8836
29137% Adult(Homer).
29138adult(homer).
29139
29140
29141% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8838
29142% !HoldsAt(Opened(GateAO),0).
29143 %  not(initially(opened(gateAO))).
29144axiom(not(initially(opened(gateAO))),
29145    []).
29146% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8839
29147% {position} 
29148
29149
29150% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8839
29151% HoldsAt(Pos(Homer,position),0) & Outside=Loc(position).
29152
29153 /*   exists([Position],
29154              (holds_at(pos(homer, Position), 0), outside=loc(Position))).
29155 */
29156
29157 /*  not(some(Some_Param, '$kolem_Fn_420')) :-
29158       (   not(holds_at(pos(homer, Some_Param), 0))
29159       ;   not(equals(outside, loc(Some_Param)))
29160       ).
29161 */
29162axiom(not(some(Some_Param, '$kolem_Fn_420')),
29163    [not(holds_at(pos(homer, Some_Param), t))]).
29164axiom(not(some(Some_Param, '$kolem_Fn_420')),
29165    [not(equals(outside, loc(Some_Param)))]).
29166
29167 /*  holds_at(pos(homer, Some_Param3), 0) :-
29168       some(Some_Param3, '$kolem_Fn_420').
29169 */
29170axiom(holds_at(pos(homer, Some_Param3), t),
29171    [some(Some_Param3, '$kolem_Fn_420')]).
29172
29173 /*  equals(outside, loc(Some_Param4)) :-
29174       some(Some_Param4, '$kolem_Fn_420').
29175 */
29176axiom(equals(outside, loc(Some_Param4)),
29177    [some(Some_Param4, '$kolem_Fn_420')]).
29178% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8840
29179% {position} 
29180
29181
29182% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8840
29183% HoldsAt(Pos(Homer,position),2) & CageA=Loc(position).
29184
29185 /*   exists([Position],
29186              (holds_at(pos(homer, Position), 2), cageA=loc(Position))).
29187 */
29188
29189 /*  not(some(Some_Param, '$kolem_Fn_421')) :-
29190       (   not(holds_at(pos(homer, Some_Param), 2))
29191       ;   not(equals(cageA, loc(Some_Param)))
29192       ).
29193 */
29194axiom(not(some(Some_Param, '$kolem_Fn_421')),
29195    [not(holds_at(pos(homer, Some_Param), t2)), b(t, t2), ignore(t+2=t2)]).
29196axiom(not(some(Some_Param, '$kolem_Fn_421')),
29197    [not(equals(cageA, loc(Some_Param)))]).
29198
29199 /*  holds_at(pos(homer, Some_Param3), 2) :-
29200       some(Some_Param3, '$kolem_Fn_421').
29201 */
29202axiom(holds_at(pos(homer, Some_Param3), t2),
29203    [some(Some_Param3, '$kolem_Fn_421'), b(t, t2), ignore(t+2=t2)]).
29204
29205 /*  equals(cageA, loc(Some_Param4)) :-
29206       some(Some_Param4, '$kolem_Fn_421').
29207 */
29208axiom(equals(cageA, loc(Some_Param4)),
29209    [some(Some_Param4, '$kolem_Fn_421')]).
29210
29211
29212% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8842
29213% [human]
29214 % HoldsAt(PosDeterminingFluent(human,1),2).
29215holds_at(posDeterminingFluent(Human,1),2).
29216
29217
29218% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8843
29219% [event,animal]
29220 % !HoldsAt(DoneBy(event,animal),2).
29221 %  not(holds_at(doneBy(Event,Animal),2)).
29222axiom(not(holds_at(doneBy(DoneBy_Param, DoneBy_Ret), t2)),
29223    [b(t, t2), ignore(t+2=t2)]).
29224
29225% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8845
29226% range time 0 2
29227% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8846
29228==> range(time,0,2).
29229
29230% range position 1 8
29231% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8847
29232==> range(position,1,8).
29233
29234% range offset 0 0
29235% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8848
29236==> range(offset,0,0).
29237%; End of file.
29238%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
29239%; FILE: examples/AkmanEtAl2004/ZooTest6.e
29240%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
29241%;
29242%; Copyright (c) 2005 IBM Corporation and others.
29243%; All rights reserved. This program and the accompanying materials
29244%; are made available under the terms of the Common Public License v1.0
29245%; which accompanies this distribution, and is available at
29246%; http://www.eclipse.org/legal/cpl-v10.html
29247%;
29248%; Contributors:
29249%; IBM - Initial implementation
29250%;
29251%; @article{Akman:2004,
29252%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
29253%;   year = "2004",
29254%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
29255%;   journal = "Artificial Intelligence",
29256%;   volume = "153",
29257%;   pages = "105--140",
29258%; }
29259%;
29260
29261% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8876
29262% option encoding 3
29263% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8877
29264:- set_ec_option(encoding, 3).29265
29266% load foundations/Root.e
29267
29268% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8879
29269% load foundations/EC.e
29270
29271% load examples/AkmanEtAl2004/ZooWorld.e
29272
29273% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8882
29274% human Homer
29275% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8883
29276==> t(human,homer).
29277
29278% elephant Jumbo
29279% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8884
29280==> t(elephant,jumbo).
29281
29282
29283% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8885
29284% Species(Homer)=HumanSpecies.
29285species(homer,humanSpecies).
29286
29287
29288% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8886
29289% Adult(Homer).
29290adult(homer).
29291
29292
29293% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8887
29294% Species(Jumbo)=ElephantSpecies.
29295species(jumbo,elephantSpecies).
29296
29297
29298% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8888
29299% Adult(Jumbo).
29300adult(jumbo).
29301
29302
29303% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8890
29304% HoldsAt(Mounted(Homer,Jumbo),0).
29305axiom(initially(mounted(homer, jumbo)),
29306    []).
29307
29308
29309% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8891
29310% HoldsAt(Pos(Jumbo,1),0).
29311axiom(initially(pos(jumbo, 1)),
29312    []).
29313
29314
29315% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8892
29316% Happens(ThrowOff(Jumbo,Homer),0).
29317axiom(happens(throwOff(jumbo, homer), t),
29318    [is_time(0)]).
29319
29320% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8894
29321% option manualrelease on
29322% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8895
29323:- set_ec_option(manualrelease, on).29324
29325
29326% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8895
29327% [human, animal]
29328 % !ReleasedAt(Mounted(human, animal),0).
29329 %  not(releasedAt(mounted(Human,Animal),0)).
29330axiom(not(releasedAt(mounted(Mounted_Param, Mounted_Ret), 0)),
29331    []).
29332
29333
29334% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8896
29335% [gate]
29336 % !ReleasedAt(Opened(gate),0).
29337 %  not(releasedAt(opened(Gate),0)).
29338axiom(not(releasedAt(opened(Opened_Ret), 0)),
29339    []).
29340
29341
29342% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8897
29343% [position]
29344 % ReleasedAt(Pos(Homer,position),0).
29345releasedAt(pos(homer,Position),0).
29346
29347
29348% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8898
29349% [position]
29350 % !ReleasedAt(Pos(Jumbo,position),0).
29351 %  not(releasedAt(pos(jumbo,Position),0)).
29352axiom(not(releasedAt(pos(jumbo, Pos_Ret), 0)),
29353    []).
29354
29355
29356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8900
29357% [human]
29358 % HoldsAt(PosDeterminingFluent(human,1),1).
29359holds_at(posDeterminingFluent(Human,1),1).
29360
29361
29362% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8901
29363% [event,animal]
29364 % !HoldsAt(DoneBy(event,animal),1).
29365 %  not(holds_at(doneBy(Event,Animal),1)).
29366axiom(not(holds_at(doneBy(DoneBy_Param, DoneBy_Ret), start)),
29367    [b(t, start), ignore(t+1=start)]).
29368
29369% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8903
29370% range time 0 1
29371% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8904
29372==> range(time,0,1).
29373
29374% range position 1 8
29375% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8905
29376==> range(position,1,8).
29377
29378% range offset 0 0
29379% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8906
29380==> range(offset,0,0).
29381%; End of file.
29382%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
29383%; FILE: examples/AkmanEtAl2004/ZooTest1.e
29384%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
29385%;
29386%; Copyright (c) 2005 IBM Corporation and others.
29387%; All rights reserved. This program and the accompanying materials
29388%; are made available under the terms of the Common Public License v1.0
29389%; which accompanies this distribution, and is available at
29390%; http://www.eclipse.org/legal/cpl-v10.html
29391%;
29392%; Contributors: 
29393%; IBM - Initial implementation
29394%;
29395%; @article{Akman:2004,
29396%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
29397%;   year = "2004",
29398%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
29399%;   journal = "Artificial Intelligence",
29400%;   volume = "153",
29401%;   pages = "105--140",
29402%; }
29403%;
29404
29405% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8934
29406% option encoding 3
29407% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8935
29408:- set_ec_option(encoding, 3).29409
29410% load foundations/Root.e
29411
29412% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8937
29413% load foundations/EC.e
29414
29415% load examples/AkmanEtAl2004/ZooWorld.e
29416
29417% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8940
29418% human Homer
29419% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8941
29420==> t(human,homer).
29421
29422% elephant Jumbo
29423% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8942
29424==> t(elephant,jumbo).
29425
29426
29427% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8943
29428% Species(Homer)=HumanSpecies.
29429species(homer,humanSpecies).
29430
29431
29432% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8944
29433% Adult(Homer).
29434adult(homer).
29435
29436
29437% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8945
29438% Species(Jumbo)=ElephantSpecies.
29439species(jumbo,elephantSpecies).
29440
29441
29442% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8946
29443% Adult(Jumbo).
29444adult(jumbo).
29445
29446
29447% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8948
29448% !HoldsAt(Opened(GateAO),0).
29449 %  not(initially(opened(gateAO))).
29450axiom(not(initially(opened(gateAO))),
29451    []).
29452
29453
29454% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8949
29455% HoldsAt(Pos(Homer,6),0).
29456axiom(initially(pos(homer, 6)),
29457    []).
29458
29459
29460% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8950
29461% [time]
29462 % HoldsAt(Pos(Jumbo,1),time).
29463holds_at(pos(jumbo,1),Time).
29464
29465
29466% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8952
29467%; goal
29468
29469
29470% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8953
29471% HoldsAt(Mounted(Homer,Jumbo),4).
29472holds_at(mounted(homer,jumbo),4).
29473
29474
29475% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8955
29476%;ABDUCE
29477%;Happens(Move(Homer,7),0).
29478%;Happens(Open(Homer,GateAO),1).
29479%;Happens(Move(Homer,4),2).
29480%;Happens(Mount(Homer,Jumbo),3).
29481% [human]
29482 
29483% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8961
29484% HoldsAt(PosDeterminingFluent(human,1),4).
29485holds_at(posDeterminingFluent(Human,1),4).
29486
29487
29488% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8962
29489% [event,animal]
29490 % !HoldsAt(DoneBy(event,animal),4).
29491 %  not(holds_at(doneBy(Event,Animal),4)).
29492axiom(not(holds_at(doneBy(DoneBy_Param, DoneBy_Ret), t4)),
29493    [b(t, t4), ignore(t+4=t4)]).
29494
29495% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8964
29496% range time 0 4
29497% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8965
29498==> range(time,0,4).
29499
29500% range position 1 8
29501% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8966
29502==> range(position,1,8).
29503
29504% range offset 0 0
29505% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8967
29506==> range(offset,0,0).
29507
29508% option timediff off
29509% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8969
29510:- set_ec_option(timediff, off).29511
29512% option modeldiff on
29513% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8970
29514:- set_ec_option(modeldiff, on).29515%; End of file.
29516%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
29517%; FILE: examples/AkmanEtAl2004/ZooTest5.2.e
29518%; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
29519%;
29520%; Copyright (c) 2005 IBM Corporation and others.
29521%; All rights reserved. This program and the accompanying materials
29522%; are made available under the terms of the Common Public License v1.0
29523%; which accompanies this distribution, and is available at
29524%; http://www.eclipse.org/legal/cpl-v10.html
29525%;
29526%; Contributors:
29527%; IBM - Initial implementation
29528%;
29529%; @article{Akman:2004,
29530%;   author = "Varol Akman and Selim T. Erdogan and Joohyung Lee and Vladimir Lifschitz and Hudson Turner",
29531%;   year = "2004",
29532%;   title = "Representing the zoo world and the traffic world in the language of the causal calculator",
29533%;   journal = "Artificial Intelligence",
29534%;   volume = "153",
29535%;   pages = "105--140",
29536%; }
29537%;
29538
29539% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8998
29540% option encoding 3
29541% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:8999
29542:- set_ec_option(encoding, 3).29543
29544% load foundations/Root.e
29545
29546% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9001
29547% load foundations/EC.e
29548
29549% load examples/AkmanEtAl2004/ZooWorld.e
29550
29551% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9004
29552% human Homer
29553% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9005
29554==> t(human,homer).
29555
29556% elephant Jumbo
29557% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9006
29558==> t(elephant,jumbo).
29559
29560% horse Silver
29561% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9007
29562==> t(horse,silver).
29563
29564
29565% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9008
29566% Species(Homer)=HumanSpecies.
29567species(homer,humanSpecies).
29568
29569
29570% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9009
29571% Adult(Homer).
29572adult(homer).
29573
29574
29575% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9010
29576% Species(Jumbo)=ElephantSpecies.
29577species(jumbo,elephantSpecies).
29578
29579
29580% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9011
29581% Adult(Jumbo).
29582adult(jumbo).
29583
29584
29585% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9012
29586% Species(Silver)=HorseSpecies.
29587species(silver,horseSpecies).
29588
29589
29590% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9013
29591% Adult(Silver).
29592adult(silver).
29593% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9015
29594% {position}
29595
29596
29597% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9016
29598% !HoldsAt(Pos(Homer,position),0) &
29599% HoldsAt(Pos(Jumbo,position),0) &
29600% HoldsAt(Pos(Homer,position),1) &
29601% !HoldsAt(Pos(Jumbo,position),1).
29602
29603 /*   exists([Position],
29604              (not(holds_at(pos(homer, Position), 0)), holds_at(pos(jumbo, Position), 0), holds_at(pos(homer, Position), 1), not(holds_at(pos(jumbo, Position), 1)))).
29605 */
29606
29607 /*  not(some(Some_Param, '$kolem_Fn_422')) :-
29608       (   holds_at(pos(homer, Some_Param), 0)
29609       ;   not(holds_at(pos(jumbo, Some_Param), 0))
29610       ;   not(holds_at(pos(homer, Some_Param), 1))
29611       ;   holds_at(pos(jumbo, Some_Param), 1)
29612       ).
29613 */
29614% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9019
29615axiom(not(some(Some_Param, '$kolem_Fn_422')),
29616    [holds_at(pos(homer, Some_Param), t)]).
29617axiom(not(some(Some_Param, '$kolem_Fn_422')),
29618    [not(holds_at(pos(jumbo, Some_Param), t))]).
29619axiom(not(some(Some_Param, '$kolem_Fn_422')),
29620   
29621    [ not(holds_at(pos(homer, Some_Param), start)),
29622      b(t, start),
29623      ignore(t+1=start)
29624    ]).
29625axiom(not(some(Some_Param, '$kolem_Fn_422')),
29626    [holds_at(pos(jumbo, Some_Param), start), b(t, start), ignore(t+1=start)]).
29627
29628 /*  not(holds_at(pos(homer, Some_Param3), 0)) :-
29629       some(Some_Param3, '$kolem_Fn_422').
29630 */
29631axiom(not(holds_at(pos(homer, Some_Param3), t)),
29632    [some(Some_Param3, '$kolem_Fn_422')]).
29633
29634 /*  holds_at(pos(jumbo, Some_Param4), 0) :-
29635       some(Some_Param4, '$kolem_Fn_422').
29636 */
29637axiom(holds_at(pos(jumbo, Some_Param4), t),
29638    [some(Some_Param4, '$kolem_Fn_422')]).
29639
29640 /*  holds_at(pos(homer, Some_Param5), 1) :-
29641       some(Some_Param5, '$kolem_Fn_422').
29642 */
29643axiom(holds_at(pos(homer, Some_Param5), start),
29644    [some(Some_Param5, '$kolem_Fn_422'), b(t, start), ignore(t+1=start)]).
29645
29646 /*  not(holds_at(pos(jumbo, Some_Param6), 1)) :-
29647       some(Some_Param6, '$kolem_Fn_422').
29648 */
29649axiom(not(holds_at(pos(jumbo, Some_Param6), start)),
29650    [some(Some_Param6, '$kolem_Fn_422'), b(t, start), ignore(t+1=start)]).
29651
29652
29653% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9020
29654% [animal,time]
29655 % !Happens(ThrowOff(animal,Homer),time).
29656 %  not(happens(throwOff(Animal,homer),Time)).
29657axiom(not(happens(throwOff(ThrowOff_Param, homer), Maptime)),
29658    []).
29659
29660
29661% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9022
29662% [human]
29663 % HoldsAt(PosDeterminingFluent(human,1),1).
29664holds_at(posDeterminingFluent(Human,1),1).
29665
29666
29667% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9023
29668% [event,animal]
29669 % !HoldsAt(DoneBy(event,animal),1).
29670 %  not(holds_at(doneBy(Event,Animal),1)).
29671axiom(not(holds_at(doneBy(DoneBy_Param, DoneBy_Ret), start)),
29672    [b(t, start), ignore(t+1=start)]).
29673
29674
29675% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9025
29676%;HoldsAt(Opened(GateAO),0).
29677%;HoldsAt(Pos(Homer,3),0).
29678%;HoldsAt(Pos(Jumbo,2),0).
29679%;HoldsAt(Pos(Silver,7),0).
29680%;Happens(Move(Jumbo,4),0).
29681%;Happens(Move(Silver,8),0).
29682%;Happens(Mount(Homer,Jumbo),0).
29683
29684% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9033
29685% range time 0 1
29686% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9034
29687==> range(time,0,1).
29688
29689% range position 1 8
29690% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9035
29691==> range(position,1,8).
29692
29693% range offset 0 0
29694% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ectest/ec_reader_test_examples.e:9036
29695==> range(offset,0,0).
29696%; End of file.