1:-include(library('ec_planner/ec_test_incl')).    2:-expects_dialect(pfc).    3 %  loading(always,'examples/Mueller2006/Chapter8/MovingRobot.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{Shanahan:1996,
   15%;   author = "Murray Shanahan",
   16%;   year = "1996",
   17%;   title = "Robotics and the common sense informatic situation",
   18%;   editor = "Wolfgang Wahlster",
   19%;   booktitle = "\uppercase{P}roceedings of the \uppercase{T}welfth \uppercase{E}uropean \uppercase{C}onference on \uppercase{A}rtificial \uppercase{I}ntelligence",
   20%;   pages = "684--688",
   21%;   address = "Chichester, UK",
   22%;   publisher = "John Wiley",
   23%; }
   24%;
   25%; @book{Mueller:2006,
   26%;   author = "Erik T. Mueller",
   27%;   year = "2006",
   28%;   title = "Commonsense Reasoning",
   29%;   address = "San Francisco",
   30%;   publisher = "Morgan Kaufmann/Elsevier",
   31%; }
   32%;
   33
   34% option renaming off
   35:- set_ec_option(renaming, off).   36
   37% load foundations/Root.e
   38
   39% load foundations/EC.e
   40
   41% sort coord: integer
   42==> subsort(coord,integer).
   43
   44% sort direction: integer
   45==> subsort(direction,integer).
   46%; 0 -> 0, 1 -> 90, 2 -> 180, 3 -> 370
   47
   48% sort robot
   49==> sort(robot).
   50
   51% robot Robot1
   52==> t(robot,robot1).
   53
   54% function Sin(direction): coord
   55 %  functional_predicate(sin(direction,coord)).
   56==> mpred_prop(sin(direction,coord),functional_predicate).
   57==> meta_argtypes(sin(direction,coord)).
   58resultIsa(sin,coord).
   59
   60% function Cos(direction): coord
   61 %  functional_predicate(cos(direction,coord)).
   62==> mpred_prop(cos(direction,coord),functional_predicate).
   63==> meta_argtypes(cos(direction,coord)).
   64resultIsa(cos,coord).
   65
   66
   67% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:47
   68% Sin(0)=0.
   69sin(0,0).
   70
   71
   72% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:48
   73% Sin(1)=1.
   74sin(1,1).
   75
   76
   77% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:49
   78% Sin(2)=2.
   79sin(2,2).
   80
   81
   82% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:50
   83% Sin(3)=3.
   84sin(3,3).
   85
   86
   87% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:52
   88% Cos(0)=1.
   89cos(0,1).
   90
   91
   92% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:53
   93% Cos(1)=2.
   94cos(1,2).
   95
   96
   97% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:54
   98% Cos(2)=3.
   99cos(2,3).
  100
  101
  102% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:55
  103% Cos(3)=4.
  104cos(3,4).
  105
  106% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:57
  107% fluent Direction(robot,direction)
  108 %  fluent(direction(robot,direction)).
  109% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:58
  110==> mpred_prop(direction(robot,direction),fluent).
  111==> meta_argtypes(direction(robot,direction)).
  112
  113% fluent Location(robot,coord,coord)
  114 %  fluent(location(robot,coord,coord)).
  115% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:59
  116==> mpred_prop(location(robot,coord,coord),fluent).
  117==> meta_argtypes(location(robot,coord,coord)).
  118
  119% event MoveLeftWheel(robot)
  120 %  event(moveLeftWheel(robot)).
  121% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:61
  122==> mpred_prop(moveLeftWheel(robot),event).
  123==> meta_argtypes(moveLeftWheel(robot)).
  124
  125% event MoveRightWheel(robot)
  126 %  event(moveRightWheel(robot)).
  127% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:62
  128==> mpred_prop(moveRightWheel(robot),event).
  129==> meta_argtypes(moveRightWheel(robot)).
  130
  131
  132% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:63
  133%; Sigma
  134% [robot,direction1,direction2,time]
  135% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:66
  136% !Happens(MoveRightWheel(robot),time) &
  137% HoldsAt(Direction(robot,direction1),time) &
  138% direction2 = (direction1-1)->
  139% Initiates(MoveLeftWheel(robot),Direction(robot,direction2),time).
  140% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:69
  141axiom(initiates(moveLeftWheel(Robot), direction(Robot, Direction2), Time),
  142   
  143    [ not(happens(moveRightWheel(Robot), Time)),
  144      holds_at(direction(Robot, Direction1), Time),
  145      equals(Direction2, Direction1-1)
  146    ]).
  147
  148
  149% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:71
  150% [robot,direction,time]
  151% !Happens(MoveRightWheel(robot),time) &
  152% HoldsAt(Direction(robot,direction),time) ->
  153% Terminates(MoveLeftWheel(robot),Direction(robot,direction),time).
  154% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:74
  155axiom(terminates(moveLeftWheel(Robot), direction(Robot, Direction), Time),
  156   
  157    [ not(happens(moveRightWheel(Robot), Time)),
  158      holds_at(direction(Robot, Direction), Time)
  159    ]).
  160
  161
  162% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:76
  163% [robot,direction1,direction2,time]
  164% !Happens(MoveLeftWheel(robot),time) &
  165% HoldsAt(Direction(robot,direction1),time) &
  166% direction2 = (direction1+1)->
  167% Initiates(MoveRightWheel(robot),Direction(robot,direction2),time).
  168% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:80
  169axiom(initiates(moveRightWheel(Robot), direction(Robot, Direction2), Time),
  170   
  171    [ not(happens(moveLeftWheel(Robot), Time)),
  172      holds_at(direction(Robot, Direction1), Time),
  173      equals(Direction2, Direction1+1)
  174    ]).
  175
  176
  177% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:82
  178% [robot,direction,time]
  179% !Happens(MoveLeftWheel(robot),time) &
  180% HoldsAt(Direction(robot,direction),time) ->
  181% Terminates(MoveRightWheel(robot),Direction(robot,direction),time).
  182% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:85
  183axiom(terminates(moveRightWheel(Robot), direction(Robot, Direction), Time),
  184   
  185    [ not(happens(moveLeftWheel(Robot), Time)),
  186      holds_at(direction(Robot, Direction), Time)
  187    ]).
  188
  189
  190% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:87
  191% [robot,direction,coord1,coord2,coord3,coord4,time]
  192% Happens(MoveLeftWheel(robot),time) &
  193% HoldsAt(Location(robot,coord1,coord2),time) &
  194% HoldsAt(Direction(robot,direction),time) &
  195% coord3 = coord1+Cos(direction) &
  196% coord4 = coord2+Sin(direction) ->
  197% Initiates(MoveRightWheel(robot),
  198%           Location(robot,coord3,coord4),
  199%           time).
  200% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:95
  201axiom(initiates(moveRightWheel(Robot), location(Robot, Coord3, Coord4), Time),
  202   
  203    [ happens(moveLeftWheel(Robot), Time),
  204      holds_at(location(Robot, Coord1, Coord2), Time),
  205      holds_at(direction(Robot, Direction), Time),
  206      equals(Coord3, Coord1+cos(Direction)),
  207      equals(Coord4, Coord2+sin(Direction))
  208    ]).
  209
  210
  211% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:97
  212% [robot,coord1,coord2,time]
  213% Happens(MoveLeftWheel(robot),time) &
  214% HoldsAt(Location(robot,coord1,coord2),time) ->
  215%; FIX: Direction not needed!!
  216%; HoldsAt(Direction(robot,direction),time) ->
  217% Terminates(MoveRightWheel(robot),Location(robot,coord1,coord2),time).
  218% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:102
  219axiom(terminates(moveRightWheel(Robot), location(Robot, Coord1, Coord2), Time),
  220   
  221    [ happens(moveLeftWheel(Robot), Time),
  222      holds_at(location(Robot, Coord1, Coord2), Time)
  223    ]).
  224
  225
  226% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:104
  227%; Delta
  228
  229
  230% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:106
  231% Happens(MoveRightWheel(Robot1),0).
  232axiom(happens(moveRightWheel(robot1), t),
  233    [is_time(0)]).
  234
  235
  236% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:107
  237% Happens(MoveLeftWheel(Robot1),1).
  238axiom(happens(moveLeftWheel(robot1), start),
  239    [is_time(1), b(t, start), ignore(t+1=start)]).
  240
  241
  242% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:108
  243% Happens(MoveRightWheel(Robot1),1).
  244axiom(happens(moveRightWheel(robot1), start),
  245    [is_time(1), b(t, start), ignore(t+1=start)]).
  246
  247
  248% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:110
  249%; Psi
  250% [robot,coord1,coord2,coord3,coord4,time]
  251% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:114
  252% HoldsAt(Location(robot,coord1,coord2),time) &
  253% HoldsAt(Location(robot,coord3,coord4),time) ->
  254% coord1=coord3 &
  255% coord2=coord4.
  256
  257 /*   if((holds_at(location(Robot, Coord1, Coord2), Time), holds_at(location(Robot, Coord3, Coord4), Time)),
  258          (Coord1=Coord3, Coord2=Coord4)).
  259 */
  260
  261 /*  not(holds_at(location(Location_Param, Equals_Param, Equals_Param9), Time6)) :-
  262       holds_at(location(Location_Param,
  263                         Equals_Ret,
  264                         Location_Ret),
  265                Time6),
  266       (   not(equals(Equals_Param, Equals_Ret))
  267       ;   not(equals(Equals_Param9, Location_Ret))
  268       ).
  269 */
  270% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:117
  271axiom(not(holds_at(location(Location_Param, Equals_Param, Equals_Param9), Time6)),
  272   
  273    [ not(equals(Equals_Param, Equals_Ret)),
  274      holds_at(location(Location_Param,
  275                        Equals_Ret,
  276                        Location_Ret),
  277               Time6)
  278    ]).
  279axiom(not(holds_at(location(Location_Param, Equals_Param, Equals_Param9), Time6)),
  280   
  281    [ not(equals(Equals_Param9, Location_Ret)),
  282      holds_at(location(Location_Param,
  283                        Equals_Ret,
  284                        Location_Ret),
  285               Time6)
  286    ]).
  287
  288 /*  not(holds_at(location(Location_Param13, Equals_Ret17, Location_Ret16), Time12)) :-
  289       holds_at(location(Location_Param13,
  290                         Equals_Param14,
  291                         Equals_Param15),
  292                Time12),
  293       (   not(equals(Equals_Param14, Equals_Ret17))
  294       ;   not(equals(Equals_Param15, Location_Ret16))
  295       ).
  296 */
  297axiom(not(holds_at(location(Location_Param13, Equals_Ret17, Location_Ret16), Time12)),
  298   
  299    [ not(equals(Equals_Param14, Equals_Ret17)),
  300      holds_at(location(Location_Param13,
  301                        Equals_Param14,
  302                        Equals_Param15),
  303               Time12)
  304    ]).
  305axiom(not(holds_at(location(Location_Param13, Equals_Ret17, Location_Ret16), Time12)),
  306   
  307    [ not(equals(Equals_Param15, Location_Ret16)),
  308      holds_at(location(Location_Param13,
  309                        Equals_Param14,
  310                        Equals_Param15),
  311               Time12)
  312    ]).
  313
  314 /*  equals(Equals_Param19, Equals_Ret21) :-
  315       holds_at(location(Location_Param20,
  316                         Equals_Param19,
  317                         Location_Ret22),
  318                Time18),
  319       holds_at(location(Location_Param20,
  320                         Equals_Ret21,
  321                         Location_Ret23),
  322                Time18).
  323 */
  324axiom(equals(Equals_Param19, Equals_Ret21),
  325   
  326    [ holds_at(location(Location_Param20,
  327                        Equals_Param19,
  328                        Location_Ret22),
  329               Time18),
  330      holds_at(location(Location_Param20,
  331                        Equals_Ret21,
  332                        Location_Ret23),
  333               Time18)
  334    ]).
  335
  336 /*  equals(Equals_Param25, Equals_Ret27) :-
  337       holds_at(location(Location_Param26, _, Equals_Param25),
  338                Time24),
  339       holds_at(location(Location_Param26, _, Equals_Ret27),
  340                Time24).
  341 */
  342axiom(equals(Equals_Param25, Equals_Ret27),
  343   
  344    [ holds_at(location(Location_Param26, _, Equals_Param25),
  345               Time24),
  346      holds_at(location(Location_Param26, _, Equals_Ret27),
  347               Time24)
  348    ]).
  349
  350
  351% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:119
  352% [robot,direction1,direction2,time]
  353% HoldsAt(Direction(robot,direction1),time) &
  354% HoldsAt(Direction(robot,direction2),time) ->
  355% direction1=direction2.
  356% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:122
  357axiom(Direction1=Direction2,
  358   
  359    [ holds_at(direction(Robot, Direction1), Time),
  360      holds_at(direction(Robot, Direction2), Time)
  361    ]).
  362
  363
  364% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:124
  365%; Gamma
  366
  367
  368% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:126
  369% HoldsAt(Location(Robot1,0,0),0).
  370axiom(initially(location(robot1, 0, 0)),
  371    []).
  372
  373
  374% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:127
  375% HoldsAt(Direction(Robot1,0),0).
  376axiom(initially(direction(robot1, 0)),
  377    []).
  378
  379% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:129
  380% completion Happens
  381% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:130
  382==> completion(happens).
  383
  384% range time 0 3
  385% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:132
  386==> range(time,0,3).
  387
  388% range coord 0 3
  389% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:133
  390==> range(coord,0,3).
  391
  392% range direction 0 3
  393% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:134
  394==> range(direction,0,3).
  395
  396% range offset 1 1
  397% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Chapter8/MovingRobot.e:135
  398==> range(offset,1,1).
  399%; End of file.