1:-include(library('ec_planner/ec_test_incl')).    2:-expects_dialect(pfc).    3 %  loading(always,'examples/Mueller2006/Exercises/TeacherTells.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%; @book{Mueller:2006,
   15%;   author = "Erik T. Mueller",
   16%;   year = "2006",
   17%;   title = "Commonsense Reasoning",
   18%;   address = "San Francisco",
   19%;   publisher = "Morgan Kaufmann/Elsevier",
   20%; }
   21%;
   22
   23% option modeldiff on
   24:- set_ec_option(modeldiff, on).   25
   26% load foundations/Root.e
   27
   28% load foundations/EC.e
   29
   30% sort agent
   31==> sort(agent).
   32
   33% sort room
   34==> sort(room).
   35
   36% sort fact
   37==> sort(fact).
   38
   39% agent Teacher, Student
   40==> t(agent,teacher).
   41==> t(agent,student).
   42
   43% room Kitchen, Classroom
   44==> t(room,kitchen).
   45==> t(room,classroom).
   46
   47% fact Fact1, Fact2
   48==> t(fact,fact1).
   49==> t(fact,fact2).
   50
   51% fluent InRoom(agent,room)
   52 %  fluent(inRoom(agent,room)).
   53==> mpred_prop(inRoom(agent,room),fluent).
   54==> meta_argtypes(inRoom(agent,room)).
   55
   56% fluent ListeningTo(agent,agent)
   57 %  fluent(listeningTo(agent,agent)).
   58==> mpred_prop(listeningTo(agent,agent),fluent).
   59==> meta_argtypes(listeningTo(agent,agent)).
   60
   61% fluent Know(agent,fact)
   62 %  fluent(know(agent,fact)).
   63==> mpred_prop(know(agent,fact),fluent).
   64==> meta_argtypes(know(agent,fact)).
   65
   66% event Tell(agent,agent,fact)
   67 %  event(tell(agent,agent,fact)).
   68==> mpred_prop(tell(agent,agent,fact),event).
   69==> meta_argtypes(tell(agent,agent,fact)).
   70
   71
   72% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:38
   73%; Sigma
   74% [agent1,agent2,fact,time]
   75% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:41
   76% (
   77% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:41
   78% {room} HoldsAt(InRoom(agent1,room),time) &
   79%         HoldsAt(InRoom(agent2,room),time)) &
   80% HoldsAt(ListeningTo(agent2,agent1),time) ->
   81% Initiates(Tell(agent1,agent2,fact),Know(agent2,fact),time).
   82
   83 /*   exists([Room],
   84             if(((holds_at(inRoom(Agent1, Room), Time), holds_at(inRoom(Agent2, Room), Time)), holds_at(listeningTo(Agent2, Agent1), Time)),
   85                initiates(tell(Agent1, Agent2, Fact),
   86                          know(Agent2, Fact),
   87                          Time))).
   88 */
   89
   90 /*  initiates(tell(Tell_Param, Know_Param, Tell_Ret), know(Know_Param, Tell_Ret), Time6) :-
   91       ( ( holds_at(inRoom(Tell_Param, Some_Param), Time6),
   92           holds_at(inRoom(Know_Param, Some_Param), Time6)
   93         ),
   94         holds_at(listeningTo(Know_Param, Tell_Param), Time6)
   95       ),
   96       some(Some_Param,
   97            '$kolem_Fn_20'(Tell_Param,
   98                           Time6,
   99                           Know_Param,
  100                           Tell_Ret)).
  101 */
  102% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:44
  103axiom(initiates(tell(Tell_Param, Know_Param, Tell_Ret), know(Know_Param, Tell_Ret), Time6),
  104   
  105    [ holds_at(inRoom(Tell_Param, Some_Param), Time6),
  106      holds_at(inRoom(Know_Param, Some_Param), Time6),
  107      holds_at(listeningTo(Know_Param, Tell_Param), Time6),
  108      some(Some_Param,
  109           '$kolem_Fn_20'(Tell_Param,
  110                          Time6,
  111                          Know_Param,
  112                          Tell_Ret))
  113    ]).
  114
  115 /*  not(holds_at(inRoom(InRoom_Param, Some_Param14), Time11)) :-
  116       holds_at(inRoom(InRoom_Param13, Some_Param14), Time11),
  117       holds_at(listeningTo(InRoom_Param13, InRoom_Param),
  118                Time11),
  119       not(initiates(tell(InRoom_Param,
  120                          InRoom_Param13,
  121                          Tell_Ret15),
  122                     know(InRoom_Param13, Tell_Ret15),
  123                     Time11)),
  124       some(Some_Param14,
  125            '$kolem_Fn_20'(InRoom_Param,
  126                           Time11,
  127                           InRoom_Param13,
  128                           Tell_Ret15)).
  129 */
  130axiom(not(holds_at(inRoom(InRoom_Param, Some_Param14), Time11)),
  131   
  132    [ holds_at(inRoom(InRoom_Param13, Some_Param14), Time11),
  133      holds_at(listeningTo(InRoom_Param13, InRoom_Param),
  134               Time11),
  135      not(initiates(tell(InRoom_Param,
  136                         InRoom_Param13,
  137                         Tell_Ret15),
  138                    know(InRoom_Param13, Tell_Ret15),
  139                    Time11)),
  140      some(Some_Param14,
  141           '$kolem_Fn_20'(InRoom_Param,
  142                          Time11,
  143                          InRoom_Param13,
  144                          Tell_Ret15))
  145    ]).
  146
  147 /*  not(holds_at(inRoom(InRoom_Param17, Some_Param19), Time16)) :-
  148       holds_at(inRoom(InRoom_Param18, Some_Param19), Time16),
  149       holds_at(listeningTo(InRoom_Param17, InRoom_Param18),
  150                Time16),
  151       not(initiates(tell(InRoom_Param18,
  152                          InRoom_Param17,
  153                          Tell_Ret20),
  154                     know(InRoom_Param17, Tell_Ret20),
  155                     Time16)),
  156       some(Some_Param19,
  157            '$kolem_Fn_20'(InRoom_Param18,
  158                           Time16,
  159                           InRoom_Param17,
  160                           Tell_Ret20)).
  161 */
  162axiom(not(holds_at(inRoom(InRoom_Param17, Some_Param19), Time16)),
  163   
  164    [ holds_at(inRoom(InRoom_Param18, Some_Param19), Time16),
  165      holds_at(listeningTo(InRoom_Param17, InRoom_Param18),
  166               Time16),
  167      not(initiates(tell(InRoom_Param18,
  168                         InRoom_Param17,
  169                         Tell_Ret20),
  170                    know(InRoom_Param17, Tell_Ret20),
  171                    Time16)),
  172      some(Some_Param19,
  173           '$kolem_Fn_20'(InRoom_Param18,
  174                          Time16,
  175                          InRoom_Param17,
  176                          Tell_Ret20))
  177    ]).
  178
  179 /*  not(holds_at(listeningTo(ListeningTo_Param, InRoom_Param23), Time21)) :-
  180       ( holds_at(inRoom(InRoom_Param23, Some_Param24), Time21),
  181         holds_at(inRoom(ListeningTo_Param, Some_Param24),
  182                  Time21)
  183       ),
  184       not(initiates(tell(InRoom_Param23,
  185                          ListeningTo_Param,
  186                          Tell_Ret25),
  187                     know(ListeningTo_Param, Tell_Ret25),
  188                     Time21)),
  189       some(Some_Param24,
  190            '$kolem_Fn_20'(InRoom_Param23,
  191                           Time21,
  192                           ListeningTo_Param,
  193                           Tell_Ret25)).
  194 */
  195axiom(not(holds_at(listeningTo(ListeningTo_Param, InRoom_Param23), Time21)),
  196   
  197    [ holds_at(inRoom(InRoom_Param23, Some_Param24), Time21),
  198      holds_at(inRoom(ListeningTo_Param, Some_Param24),
  199               Time21),
  200      not(initiates(tell(InRoom_Param23,
  201                         ListeningTo_Param,
  202                         Tell_Ret25),
  203                    know(ListeningTo_Param, Tell_Ret25),
  204                    Time21)),
  205      some(Some_Param24,
  206           '$kolem_Fn_20'(InRoom_Param23,
  207                          Time21,
  208                          ListeningTo_Param,
  209                          Tell_Ret25))
  210    ]).
  211
  212 /*  not(some(Some_Param27, '$kolem_Fn_20'(Fn_20_Param, Time26, Know_Param29, Fn_20_Ret))) :-
  213       not(initiates(tell(Fn_20_Param, Know_Param29, Fn_20_Ret),
  214                     know(Know_Param29, Fn_20_Ret),
  215                     Time26)),
  216       ( holds_at(inRoom(Fn_20_Param, Some_Param27), Time26),
  217         holds_at(inRoom(Know_Param29, Some_Param27), Time26)
  218       ),
  219       holds_at(listeningTo(Know_Param29, Fn_20_Param), Time26).
  220 */
  221axiom(not(some(Some_Param27, '$kolem_Fn_20'(Fn_20_Param, Time26, Know_Param29, Fn_20_Ret))),
  222   
  223    [ not(initiates(tell(Fn_20_Param, Know_Param29, Fn_20_Ret),
  224                    know(Know_Param29, Fn_20_Ret),
  225                    Time26)),
  226      holds_at(inRoom(Fn_20_Param, Some_Param27), Time26),
  227      holds_at(inRoom(Know_Param29, Some_Param27), Time26),
  228      holds_at(listeningTo(Know_Param29, Fn_20_Param), Time26)
  229    ]).
  230
  231
  232% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:46
  233%; Delta
  234
  235
  236% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:48
  237% Happens(Tell(Teacher,Student,Fact1),0).
  238axiom(happens(tell(teacher, student, fact1), t),
  239    [is_time(0)]).
  240
  241
  242% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:50
  243%; Psi
  244% [agent,room1,room2,time]
  245% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:53
  246% HoldsAt(InRoom(agent,room1),time) &
  247% HoldsAt(InRoom(agent,room2),time) ->
  248% room1 = room2.
  249% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:55
  250axiom(Room1=Room2,
  251   
  252    [ holds_at(inRoom(Agent, Room1), Time),
  253      holds_at(inRoom(Agent, Room2), Time)
  254    ]).
  255
  256
  257% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:57
  258%; Gamma
  259% [agent,fact]
  260 % !HoldsAt(Know(agent,fact),0).
  261 %  not(initially(know(Agent,Fact))).
  262% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:59
  263axiom(not(initially(know(Know_Param, Know_Ret))),
  264    []).
  265
  266
  267% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:60
  268% [agent1,agent2]
  269 % HoldsAt(ListeningTo(agent1,agent2),0).
  270axiom(initially(listeningTo(Agent1, Agent2)),
  271    []).
  272
  273
  274% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:61
  275% [agent]
  276 % HoldsAt(InRoom(agent,Classroom),0).
  277axiom(initially(inRoom(Agent, classroom)),
  278    []).
  279
  280% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:63
  281% completion Happens
  282% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:64
  283==> completion(happens).
  284
  285% range time 0 1
  286% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:66
  287==> range(time,0,1).
  288
  289% range offset 1 1
  290% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/examples/Mueller2006/Exercises/TeacherTells.e:67
  291==> range(offset,1,1).
  292%; End of file.