1:-include(library('ec_planner/ec_test_incl')).    2:-expects_dialect(pfc).    3 %  loading(always,'examples/Mueller2004b/Leaf.e').
    4%;
    5%; Copyright (c) 2005 IBM Corporation and others.
    6%; All rights reserved. This program and the accompanying materials
    7%; are made available under the terms of the Common Public License v1.0
    8%; which accompanies this distribution, and is available at
    9%; http://www.eclipse.org/legal/cpl-v10.html
   10%;
   11%; Contributors:
   12%; IBM - Initial implementation
   13%;
   14%; @inproceedings{Mueller:2004b,
   15%;   author = "Erik T. Mueller",
   16%;   year = "2004",
   17%;   title = "A tool for satisfiability-based commonsense reasoning in the event calculus",
   18%;   editor = "Valerie Barr and Zdravko Markov",
   19%;   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",
   20%;   pages = "147--152",
   21%;   address = "Menlo Park, CA",
   22%;   publisher = "AAAI Press",
   23%; }
   24%;
   25
   26% option trajectory on
   27:- set_ec_option(trajectory, on).   28
   29% load foundations/Root.e
   30
   31% load foundations/EC.e
   32
   33% sort object
   34==> sort(object).
   35
   36% sort height: integer
   37==> subsort(height,integer).
   38
   39% fluent Height(object,height)
   40 %  fluent(height(object,height)).
   41==> mpred_prop(height(object,height),fluent).
   42==> meta_argtypes(height(object,height)).
   43
   44% fluent Falling(object)
   45 %  fluent(falling(object)).
   46==> mpred_prop(falling(object),fluent).
   47==> meta_argtypes(falling(object)).
   48
   49% event StartFalling(object)
   50 %  event(startFalling(object)).
   51==> mpred_prop(startFalling(object),event).
   52==> meta_argtypes(startFalling(object)).
   53
   54% event HitsGround(object)
   55 %  event(hitsGround(object)).
   56==> mpred_prop(hitsGround(object),event).
   57==> meta_argtypes(hitsGround(object)).
   58
   59
   60% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:35
   61% [object,height1,height2,time]
   62% HoldsAt(Height(object,height1),time) &
   63% HoldsAt(Height(object,height2),time) ->
   64% height1=height2.
   65% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:38
   66axiom(Height1=Height2,
   67   
   68    [ holds_at(height(Object, Height1), Time),
   69      holds_at(height(Object, Height2), Time)
   70    ]).
   71
   72
   73% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:40
   74% [object,time]
   75% Initiates(StartFalling(object),Falling(object),time).
   76% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:41
   77axiom(initiates(startFalling(Object), falling(Object), Time),
   78    []).
   79
   80
   81% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:43
   82% [object,height,time]
   83% Releases(StartFalling(object),Height(object,height),time).
   84% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:44
   85axiom(releases(startFalling(Object), height(Object, Height), Time),
   86    []).
   87
   88
   89% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:46
   90% [object,height1,height2,offset,time]
   91% HoldsAt(Height(object,height1),time) &
   92% height2=height1-offset ->
   93% Trajectory(Falling(object),time,Height(object,height2),offset).
   94% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:49
   95axiom(trajectory(falling(Object), Time, height(Object, Height2), Offset),
   96   
   97    [ holds_at(height(Object, Height1), Time),
   98      equals(Height2, Height1-Offset)
   99    ]).
  100
  101
  102% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:51
  103% [object,time]
  104% HoldsAt(Falling(object),time) &
  105% HoldsAt(Height(object,0),time) ->
  106% Happens(HitsGround(object),time).
  107% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:54
  108axiom(happens(hitsGround(Object), Time),
  109   
  110    [ holds_at(falling(Object), Time),
  111      holds_at(height(Object, 0), Time)
  112    ]).
  113
  114
  115% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:56
  116%;[object,height1,height2,time]
  117%;HoldsAt(Height(object,height1),time) &
  118%;height1 != height2 ->
  119%;Terminates(HitsGround(object),Height(object,height2),time).
  120% [object,height,time]
  121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:62
  122% HoldsAt(Height(object,height),time) ->
  123% Initiates(HitsGround(object),Height(object,height),time).
  124% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:63
  125axiom(initiates(hitsGround(Object), height(Object, Height), Time),
  126    [holds_at(height(Object, Height), Time)]).
  127
  128
  129% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:65
  130% [object,time]
  131% Terminates(HitsGround(object),Falling(object),time).
  132% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:66
  133axiom(terminates(hitsGround(Object), falling(Object), Time),
  134    []).
  135
  136% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:68
  137% object Leaf
  138% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:69
  139==> t(object,leaf).
  140
  141
  142% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:70
  143% !HoldsAt(Falling(Leaf),0).
  144 %  not(initially(falling(leaf))).
  145axiom(not(initially(falling(leaf))),
  146    []).
  147
  148
  149% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:71
  150% HoldsAt(Height(Leaf,4),0).
  151axiom(initially(height(leaf, 4)),
  152    []).
  153
  154
  155% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:72
  156% Happens(StartFalling(Leaf),2).
  157axiom(happens(startFalling(leaf), t2),
  158    [is_time(2), b(t, t2), ignore(t+2=t2)]).
  159
  160% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:74
  161% completion Happens
  162% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:75
  163==> completion(happens).
  164
  165% range time 0 7
  166% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:77
  167==> range(time,0,7).
  168
  169% range offset 1 4
  170% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:78
  171==> range(offset,1,4).
  172
  173% range height 0 4
  174% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2004b/Leaf.e:79
  175==> range(height,0,4).
  176%; End of file.