1:-include(library('ec_planner/ec_test_incl')).    2:-expects_dialect(pfc).    3 %  loading(always,'ecnet/Fire.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%; fire
   15%;
   16%; agent sets fire to physobj with burn time offset.
   17
   18% event SetFireTo(agent,physobj,fire,offset)
   19 %  event(setFireTo(agent,physobj,fire,offset)).
   20==> mpred_prop(setFireTo(agent,physobj,fire,offset),event).
   21==> meta_argtypes(setFireTo(agent,physobj,fire,offset)).
   22
   23
   24% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:16
   25%; An effect axioms states that
   26%; if an agent sets a fire to a physical object with a burn time,
   27%; the physical object will be burning with the fire and burn time:
   28% [agent,physobj,fire,offset,time]
   29% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:20
   30% Initiates(SetFireTo(agent,physobj,fire,offset),
   31%           Burning(physobj,fire,offset),
   32%           time).
   33% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:22
   34axiom(initiates(setFireTo(Agent, Physobj, Fire, Offset), burning(Physobj, Fire, Offset), Time),
   35    []).
   36
   37
   38% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:24
   39%; agent puts out fire on physobj.
   40
   41% event PutOutFire(agent,physobj,fire)
   42 %  event(putOutFire(agent,physobj,fire)).
   43% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:26
   44==> mpred_prop(putOutFire(agent,physobj,fire),event).
   45==> meta_argtypes(putOutFire(agent,physobj,fire)).
   46
   47
   48% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:27
   49%; An effect axiom states that
   50%; if an agent puts out a fire on a physical object,
   51%; the physical object will no longer be burning:
   52% [agent,physobj,fire,offset,time]
   53% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:31
   54% Terminates(PutOutFire(agent,physobj,fire),
   55%            Burning(physobj,fire,offset),
   56%            time).
   57% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:33
   58axiom(terminates(putOutFire(Agent, Physobj, Fire), burning(Physobj, Fire, Offset), Time),
   59    []).
   60
   61
   62% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:35
   63%; A precondition axiom states that
   64%; for an agent to set fire to a physical object,
   65%; there must be a location such that
   66%; the agent is at the location and
   67%; the physical object is at the location:
   68% [agent,fire,physobj,offset,time]
   69% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:41
   70% Happens(SetFireTo(agent,physobj,fire,offset),time) ->
   71% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:42
   72% {location}%  HoldsAt(At(agent,location),time) &
   73%            HoldsAt(At(physobj,location),time).
   74
   75 /*   exists([Location],
   76             if(happens(setFireTo(Agent,
   77                                  Physobj,
   78                                  Fire,
   79                                  Offset),
   80                        Time),
   81                 (holds_at(at(Agent, Location), Time), holds_at(at(Physobj, Location), Time)))).
   82 */
   83
   84 /*  not(some(Location8, '$kolem_Fn_141'(Fn_141_Param, At_Param, A, SetFireTo_Ret, Maptime))) :-
   85       happens(setFireTo(Fn_141_Param,
   86                         At_Param,
   87                         A,
   88                         SetFireTo_Ret),
   89               Maptime),
   90       (   not(holds_at(at(Fn_141_Param, Location8), Maptime))
   91       ;   not(holds_at(at(At_Param, Location8), Maptime))
   92       ).
   93 */
   94% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:43
   95axiom(not(some(Location8, '$kolem_Fn_141'(Fn_141_Param, At_Param, A, SetFireTo_Ret, Maptime))),
   96   
   97    [ not(holds_at(at(Fn_141_Param, Location8), Maptime)),
   98      happens(setFireTo(Fn_141_Param,
   99                        At_Param,
  100                        A,
  101                        SetFireTo_Ret),
  102              Maptime)
  103    ]).
  104axiom(not(some(Location8, '$kolem_Fn_141'(Fn_141_Param, At_Param, A, SetFireTo_Ret, Maptime))),
  105   
  106    [ not(holds_at(at(At_Param, Location8), Maptime)),
  107      happens(setFireTo(Fn_141_Param,
  108                        At_Param,
  109                        A,
  110                        SetFireTo_Ret),
  111              Maptime)
  112    ]).
  113
  114 /*  not(happens(setFireTo(SetFireTo_Param, At_Param15, A, SetFireTo_Ret16), Maptime12)) :-
  115       (   not(holds_at(at(SetFireTo_Param, Location13),
  116                        Maptime12))
  117       ;   not(holds_at(at(At_Param15, Location13), Maptime12))
  118       ),
  119       some(Location13,
  120            '$kolem_Fn_141'(SetFireTo_Param,
  121                            At_Param15,
  122                            A,
  123                            SetFireTo_Ret16,
  124                            Maptime12)).
  125 */
  126axiom(not(happens(setFireTo(SetFireTo_Param, At_Param15, A, SetFireTo_Ret16), Maptime12)),
  127   
  128    [ not(holds_at(at(SetFireTo_Param, Location13), Maptime12)),
  129      some(Location13,
  130           '$kolem_Fn_141'(SetFireTo_Param,
  131                           At_Param15,
  132                           A,
  133                           SetFireTo_Ret16,
  134                           Maptime12))
  135    ]).
  136axiom(not(happens(setFireTo(SetFireTo_Param, At_Param15, A, SetFireTo_Ret16), Maptime12)),
  137   
  138    [ not(holds_at(at(At_Param15, Location13), Maptime12)),
  139      some(Location13,
  140           '$kolem_Fn_141'(SetFireTo_Param,
  141                           At_Param15,
  142                           A,
  143                           SetFireTo_Ret16,
  144                           Maptime12))
  145    ]).
  146
  147 /*  holds_at(at(At_Param19, Location17), Time18) :-
  148       happens(setFireTo(At_Param19, A, B, SetFireTo_Ret20),
  149               Time18),
  150       some(Location17,
  151            '$kolem_Fn_141'(At_Param19,
  152                            A,
  153                            B,
  154                            SetFireTo_Ret20,
  155                            Time18)).
  156 */
  157axiom(holds_at(at(At_Param19, Location17), Time18),
  158   
  159    [ happens(setFireTo(At_Param19,
  160                        A,
  161                        B,
  162                        SetFireTo_Ret20),
  163              Time18),
  164      some(Location17,
  165           '$kolem_Fn_141'(At_Param19,
  166                           A,
  167                           B,
  168                           SetFireTo_Ret20,
  169                           Time18))
  170    ]).
  171
  172 /*  holds_at(at(At_Param23, Location21), Time22) :-
  173       happens(setFireTo(SetFireTo_Param24,
  174                         At_Param23,
  175                         A,
  176                         SetFireTo_Ret25),
  177               Time22),
  178       some(Location21,
  179            '$kolem_Fn_141'(SetFireTo_Param24,
  180                            At_Param23,
  181                            A,
  182                            SetFireTo_Ret25,
  183                            Time22)).
  184 */
  185axiom(holds_at(at(At_Param23, Location21), Time22),
  186   
  187    [ happens(setFireTo(SetFireTo_Param24,
  188                        At_Param23,
  189                        A,
  190                        SetFireTo_Ret25),
  191              Time22),
  192      some(Location21,
  193           '$kolem_Fn_141'(SetFireTo_Param24,
  194                           At_Param23,
  195                           A,
  196                           SetFireTo_Ret25,
  197                           Time22))
  198    ]).
  199
  200
  201% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:45
  202%; A precondition axiom states that
  203%; for an agent to put out a fire on a physical object,
  204%; there must be a location such that
  205%; the agent is at the location and
  206%; the physical object is at the location:
  207% [agent,fire,physobj,time]
  208% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:51
  209% Happens(PutOutFire(agent,physobj,fire),time) ->
  210% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:52
  211% {location}%  HoldsAt(At(agent,location),time) &
  212%            HoldsAt(At(physobj,location),time).
  213
  214 /*   exists([Location],
  215             if(happens(putOutFire(Agent, Physobj, Fire),
  216                        Time),
  217                 (holds_at(at(Agent, Location), Time), holds_at(at(Physobj, Location), Time)))).
  218 */
  219
  220 /*  not(some(Location7, '$kolem_Fn_142'(Fn_142_Param, At_Param, PutOutFire_Ret, Maptime))) :-
  221       happens(putOutFire(Fn_142_Param, At_Param, PutOutFire_Ret),
  222               Maptime),
  223       (   not(holds_at(at(Fn_142_Param, Location7), Maptime))
  224       ;   not(holds_at(at(At_Param, Location7), Maptime))
  225       ).
  226 */
  227% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:53
  228axiom(not(some(Location7, '$kolem_Fn_142'(Fn_142_Param, At_Param, PutOutFire_Ret, Maptime))),
  229   
  230    [ not(holds_at(at(Fn_142_Param, Location7), Maptime)),
  231      happens(putOutFire(Fn_142_Param,
  232                         At_Param,
  233                         PutOutFire_Ret),
  234              Maptime)
  235    ]).
  236axiom(not(some(Location7, '$kolem_Fn_142'(Fn_142_Param, At_Param, PutOutFire_Ret, Maptime))),
  237   
  238    [ not(holds_at(at(At_Param, Location7), Maptime)),
  239      happens(putOutFire(Fn_142_Param,
  240                         At_Param,
  241                         PutOutFire_Ret),
  242              Maptime)
  243    ]).
  244
  245 /*  not(happens(putOutFire(PutOutFire_Param, At_Param14, PutOutFire_Ret15), Maptime11)) :-
  246       (   not(holds_at(at(PutOutFire_Param, Location12),
  247                        Maptime11))
  248       ;   not(holds_at(at(At_Param14, Location12), Maptime11))
  249       ),
  250       some(Location12,
  251            '$kolem_Fn_142'(PutOutFire_Param,
  252                            At_Param14,
  253                            PutOutFire_Ret15,
  254                            Maptime11)).
  255 */
  256axiom(not(happens(putOutFire(PutOutFire_Param, At_Param14, PutOutFire_Ret15), Maptime11)),
  257   
  258    [ not(holds_at(at(PutOutFire_Param, Location12),
  259                   Maptime11)),
  260      some(Location12,
  261           '$kolem_Fn_142'(PutOutFire_Param,
  262                           At_Param14,
  263                           PutOutFire_Ret15,
  264                           Maptime11))
  265    ]).
  266axiom(not(happens(putOutFire(PutOutFire_Param, At_Param14, PutOutFire_Ret15), Maptime11)),
  267   
  268    [ not(holds_at(at(At_Param14, Location12), Maptime11)),
  269      some(Location12,
  270           '$kolem_Fn_142'(PutOutFire_Param,
  271                           At_Param14,
  272                           PutOutFire_Ret15,
  273                           Maptime11))
  274    ]).
  275
  276 /*  holds_at(at(At_Param18, Location16), Time17) :-
  277       happens(putOutFire(At_Param18, A, PutOutFire_Ret19),
  278               Time17),
  279       some(Location16,
  280            '$kolem_Fn_142'(At_Param18,
  281                            A,
  282                            PutOutFire_Ret19,
  283                            Time17)).
  284 */
  285axiom(holds_at(at(At_Param18, Location16), Time17),
  286   
  287    [ happens(putOutFire(At_Param18, A, PutOutFire_Ret19),
  288              Time17),
  289      some(Location16,
  290           '$kolem_Fn_142'(At_Param18,
  291                           A,
  292                           PutOutFire_Ret19,
  293                           Time17))
  294    ]).
  295
  296 /*  holds_at(at(At_Param22, Location20), Time21) :-
  297       happens(putOutFire(PutOutFire_Param23,
  298                          At_Param22,
  299                          PutOutFire_Ret24),
  300               Time21),
  301       some(Location20,
  302            '$kolem_Fn_142'(PutOutFire_Param23,
  303                            At_Param22,
  304                            PutOutFire_Ret24,
  305                            Time21)).
  306 */
  307axiom(holds_at(at(At_Param22, Location20), Time21),
  308   
  309    [ happens(putOutFire(PutOutFire_Param23,
  310                         At_Param22,
  311                         PutOutFire_Ret24),
  312              Time21),
  313      some(Location20,
  314           '$kolem_Fn_142'(PutOutFire_Param23,
  315                           At_Param22,
  316                           PutOutFire_Ret24,
  317                           Time21))
  318    ]).
  319
  320
  321% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:55
  322%; physobj is burning with fire and burn time offset.
  323
  324% fluent Burning(physobj,fire,offset)
  325 %  fluent(burning(physobj,fire,offset)).
  326% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:57
  327==> mpred_prop(burning(physobj,fire,offset),fluent).
  328==> meta_argtypes(burning(physobj,fire,offset)).
  329
  330
  331% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:58
  332%; A state constraint says that a physical object burning with
  333%; a fire has at most one burn time at a time:
  334% [physobj,fire,offset1,offset2,time]
  335% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:61
  336% HoldsAt(Burning(physobj,fire,offset1),time) &
  337% HoldsAt(Burning(physobj,fire,offset2),time) ->
  338% offset1=offset2.
  339% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:63
  340axiom(Offset1=Offset2,
  341   
  342    [ holds_at(burning(Physobj, Fire, Offset1), Time),
  343      holds_at(burning(Physobj, Fire, Offset2), Time)
  344    ]).
  345
  346
  347% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:65
  348%; The burn time of physobj is decremented.
  349
  350% event DecrementBurning(physobj)
  351 %  event(decrementBurning(physobj)).
  352% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:67
  353==> mpred_prop(decrementBurning(physobj),event).
  354==> meta_argtypes(decrementBurning(physobj)).
  355
  356
  357% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:68
  358%; A trigger axiom states that
  359%; if a physical object is burning with a fire and a burn time and
  360%; the burn time is greater than zero,
  361%; the burn time of the physical object is decremented:
  362% [physobj,fire,offset,time]
  363% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:73
  364% HoldsAt(Burning(physobj,fire,offset),time) &
  365% (offset > 0) ->
  366% Happens(DecrementBurning(physobj),time).
  367% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:75
  368axiom(happens(decrementBurning(Physobj), Time),
  369   
  370    [ holds_at(burning(Physobj, Fire, Offset), Time),
  371      comparison(Offset, 0, >)
  372    ]).
  373
  374
  375% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:77
  376%; An effect axiom states that if a physical object is
  377%; burning with a fire and a burn time, and the burn time of a physical
  378%; object is decremented, the burn time of the physical
  379%; object will be the burn time minus one:
  380% [physobj,fire,offset1,offset2,time]
  381% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:82
  382% HoldsAt(Burning(physobj,fire,offset1),time) &
  383% offset2 = offset1-1 ->
  384% Initiates(DecrementBurning(physobj),
  385%           Burning(physobj,fire,offset2),
  386%           time).
  387% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:86
  388axiom(initiates(decrementBurning(Physobj), burning(Physobj, Fire, Offset2), Time),
  389   
  390    [ holds_at(burning(Physobj, Fire, Offset1), Time),
  391      equals(Offset2, Offset1-1)
  392    ]).
  393
  394
  395% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:88
  396%; An effect axiom states that if a physical object is
  397%; burning with a fire and a burn time, and the burn time of a physical
  398%; object is decremented, the burn time of the physical
  399%; object will no longer be the burn time:
  400% [physobj,fire,offset,time]
  401% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:93
  402% HoldsAt(Burning(physobj,fire,offset),time) ->
  403% Terminates(DecrementBurning(physobj),
  404%            Burning(physobj,fire,offset),
  405%            time).
  406% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:96
  407axiom(terminates(decrementBurning(Physobj), burning(Physobj, Fire, Offset), Time),
  408    [holds_at(burning(Physobj, Fire, Offset), Time)]).
  409
  410
  411% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:98
  412%; A trigger axiom states that
  413%; if a physical object is burning with a fire and a burn time
  414%; that is not equal to zero, the fire will damage the
  415%; physical object:
  416% [physobj,fire,offset,time]
  417% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:103
  418% offset!=% 0 &
  419% HoldsAt(Burning(physobj,fire,offset),time) &
  420% HoldsAt(Intact(physobj),time) ->
  421% Happens(Damage(fire,physobj),time).
  422% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:106
  423axiom(happens(damage(Fire, Physobj), Time),
  424   
  425    [ dif(Offset, 0),
  426      holds_at(burning(Physobj, Fire, Offset), Time),
  427      holds_at(intact(Physobj), Time)
  428    ]).
  429
  430
  431% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:108
  432%; A trigger axiom states that
  433%; if a physical object is burning with a fire and a burn time
  434%; that is equal to zero, the fire will destroy the
  435%; physical object:
  436% [physobj,fire,time]
  437% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:113
  438% HoldsAt(Burning(physobj,fire,0),time) &
  439% !HoldsAt(Destroyed(physobj),time) ->
  440% Happens(Destroy(fire,physobj),time).
  441% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:115
  442axiom(happens(destroy(Fire, Physobj), Time),
  443   
  444    [ holds_at(burning(Physobj, Fire, 0), Time),
  445      not(holds_at(destroyed(Physobj), Time))
  446    ]).
  447
  448
  449% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:117
  450%; An effect axiom states that if a fire destroys a physical
  451%; object, the physical object will no longer be burning:
  452% [physobj,fire,offset,time]
  453% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:120
  454% Terminates(Destroy(fire,physobj),
  455%            Burning(physobj,fire,offset),
  456%            time).
  457% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:122
  458axiom(terminates(destroy(Fire, Physobj), burning(Physobj, Fire, Offset), Time),
  459    []).
  460
  461
  462% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Fire.e:124
  463%; End of file.