1:-include(library('ec_planner/ec_test_incl')).    2:-expects_dialect(pfc).    3 %  loading(always,'ecnet/Gun.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
   15% fluent Loaded(gun,bullet)
   16 %  fluent(loaded(gun,bullet)).
   17==> mpred_prop(loaded(gun,bullet),fluent).
   18==> meta_argtypes(loaded(gun,bullet)).
   19
   20% noninertial Loaded
   21==> noninertial(loaded).
   22
   23
   24% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:14
   25% [gun,bullet,time]
   26% HoldsAt(Inside(bullet,gun),time) <->
   27% HoldsAt(Loaded(gun,bullet),time).
   28
   29 /*  holds_at(inside(Bullet, Gun), Time) <->
   30       holds_at(loaded(Gun, Bullet), Time).
   31 */
   32% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:16
   33axiom(holds_at(inside(Bullet, Gun), Time),
   34    [holds_at(loaded(Gun, Bullet), Time)]).
   35axiom(holds_at(loaded(Gun, Bullet), Time),
   36    [holds_at(inside(Bullet, Gun), Time)]).
   37
   38% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:18
   39% event Shoot(agent,gun,object)
   40 %  event(shoot(agent,gun,object)).
   41% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:19
   42==> mpred_prop(shoot(agent,gun,object),event).
   43==> meta_argtypes(shoot(agent,gun,object)).
   44
   45% event ShootInjure(agent,gun,agent)
   46 %  event(shootInjure(agent,gun,agent)).
   47% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:21
   48==> mpred_prop(shootInjure(agent,gun,agent),event).
   49==> meta_argtypes(shootInjure(agent,gun,agent)).
   50
   51% event ShootKill(agent,gun,agent)
   52 %  event(shootKill(agent,gun,agent)).
   53% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:23
   54==> mpred_prop(shootKill(agent,gun,agent),event).
   55==> meta_argtypes(shootKill(agent,gun,agent)).
   56
   57% event ShootDamage(agent,gun,physobj)
   58 %  event(shootDamage(agent,gun,physobj)).
   59% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:25
   60==> mpred_prop(shootDamage(agent,gun,physobj),event).
   61==> meta_argtypes(shootDamage(agent,gun,physobj)).
   62
   63% event ShootDestroy(agent,gun,physobj)
   64 %  event(shootDestroy(agent,gun,physobj)).
   65% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:27
   66==> mpred_prop(shootDestroy(agent,gun,physobj),event).
   67==> meta_argtypes(shootDestroy(agent,gun,physobj)).
   68
   69
   70% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:28
   71% [agent,gun,bullet,object,time]
   72% HoldsAt(Inside(bullet,gun),time) ->
   73% Terminates(Shoot(agent,gun,object),
   74%            Inside(bullet,gun),
   75%            time).
   76% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:32
   77axiom(terminates(shoot(Agent, Gun, Object), inside(Bullet, Gun), Time),
   78    [holds_at(inside(Bullet, Gun), Time)]).
   79
   80
   81% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:34
   82% [agent,gun,bullet,object,location1,location2,time]
   83% HoldsAt(Inside(bullet,gun),time) &
   84% HoldsAt(At(gun,location1),time) &
   85% location1 != location2 ->
   86% Terminates(Shoot(agent,gun,object),At(bullet,location2),time).
   87% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:38
   88axiom(terminates(shoot(Agent, Gun, Object), at(Bullet, Location2), Time),
   89   
   90    [ holds_at(inside(Bullet, Gun), Time),
   91      holds_at(at(Gun, Location1), Time),
   92      { dif(Location1, Location2)
   93      }
   94    ]).
   95
   96
   97% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:40
   98% [agent,gun,bullet,object,location,time]
   99% HoldsAt(At(object,location),time) &
  100% HoldsAt(Inside(bullet,gun),time) ->
  101% Initiates(Shoot(agent,gun,object),At(bullet,location),time).
  102% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:43
  103axiom(initiates(shoot(Agent, Gun, Object), at(Bullet, Location), Time),
  104   
  105    [ holds_at(at(Object, Location), Time),
  106      holds_at(inside(Bullet, Gun), Time)
  107    ]).
  108
  109
  110% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:45
  111% [agent,gun,object,time]
  112% Happens(Shoot(agent,gun,object),time) ->
  113% HoldsAt(Holding(agent,gun),time) &
  114% ({bullet} HoldsAt(Loaded(gun,bullet),time)) &
  115% ({location} HoldsAt(At(agent,location),time) &
  116%             HoldsAt(At(object,location),time)).
  117% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:50
  118axiom(requires(shoot(Agent, Gun, Object), Time),
  119   
  120    [ holds_at(holding(Agent, Gun), Time),
  121      holds_at(loaded(Gun, Bullet), Time),
  122      holds_at(at(Agent, Location), Time),
  123      holds_at(at(Object, Location), Time)
  124    ]).
  125
  126
  127% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:52
  128% [agent1,gun,agent2,time]
  129% Happens(Shoot(agent1,gun,agent2),time) ->
  130% Happens(ShootInjure(agent1,gun,agent2),time) |
  131% Happens(ShootKill(agent1,gun,agent2),time).
  132
  133 /*   if(happens(shoot(Agent1, Gun, Agent2), Time),
  134          (happens(shootInjure(Agent1, Gun, Agent2), Time);happens(shootKill(Agent1, Gun, Agent2), Time))).
  135 */
  136
  137 /*  happens(shootInjure(ShootInjure_Param, A, ShootInjure_Ret), Maptime) :-
  138       not(happens(shootKill(ShootInjure_Param,
  139                             A,
  140                             ShootInjure_Ret),
  141                   Maptime)),
  142       happens(shoot(ShootInjure_Param, A, ShootInjure_Ret),
  143               Maptime).
  144 */
  145% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:55
  146axiom(happens(shootInjure(ShootInjure_Param, A, ShootInjure_Ret), Maptime),
  147   
  148    [ not(happens(shootKill(ShootInjure_Param,
  149                            A,
  150                            ShootInjure_Ret),
  151                  Maptime)),
  152      happens(shoot(ShootInjure_Param, A, ShootInjure_Ret),
  153              Maptime)
  154    ]).
  155
  156 /*  happens(shootKill(ShootKill_Param, A, ShootKill_Ret), Maptime7) :-
  157       not(happens(shootInjure(ShootKill_Param, A, ShootKill_Ret),
  158                   Maptime7)),
  159       happens(shoot(ShootKill_Param, A, ShootKill_Ret),
  160               Maptime7).
  161 */
  162axiom(happens(shootKill(ShootKill_Param, A, ShootKill_Ret), Maptime7),
  163   
  164    [ not(happens(shootInjure(ShootKill_Param,
  165                              A,
  166                              ShootKill_Ret),
  167                  Maptime7)),
  168      happens(shoot(ShootKill_Param, A, ShootKill_Ret),
  169              Maptime7)
  170    ]).
  171
  172 /*  not(happens(shoot(Shoot_Param, A, Shoot_Ret), Maptime10)) :-
  173       not(happens(shootInjure(Shoot_Param, A, Shoot_Ret),
  174                   Maptime10)),
  175       not(happens(shootKill(Shoot_Param, A, Shoot_Ret),
  176                   Maptime10)).
  177 */
  178axiom(not(happens(shoot(Shoot_Param, A, Shoot_Ret), Maptime10)),
  179   
  180    [ not(happens(shootInjure(Shoot_Param, A, Shoot_Ret),
  181                  Maptime10)),
  182      not(happens(shootKill(Shoot_Param, A, Shoot_Ret),
  183                  Maptime10))
  184    ]).
  185
  186
  187% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:57
  188% [agent1,gun,bullet,agent2,time]
  189% HoldsAt(Inside(bullet,gun),time) &
  190% Happens(ShootKill(agent1,gun,agent2),time) ->
  191% Happens(Kill(bullet,agent2),time).
  192% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:60
  193axiom(happens(kill(Bullet, Agent2), Time),
  194   
  195    [ holds_at(inside(Bullet, Gun), Time),
  196      happens(shootKill(Agent1, Gun, Agent2), Time)
  197    ]).
  198
  199
  200% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:62
  201% [agent1,gun,bullet,agent2,time]
  202% HoldsAt(Inside(bullet,gun),time) &
  203% Happens(ShootInjure(agent1,gun,agent2),time) ->
  204% Happens(Injure(bullet,agent2),time).
  205% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:65
  206axiom(happens(injure(Bullet, Agent2), Time),
  207   
  208    [ holds_at(inside(Bullet, Gun), Time),
  209      happens(shootInjure(Agent1, Gun, Agent2), Time)
  210    ]).
  211
  212
  213% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:67
  214% [agent,gun,physobj,time]
  215% Happens(Shoot(agent,gun,physobj),time) ->
  216% Happens(ShootDamage(agent,gun,physobj),time) |
  217% Happens(ShootDestroy(agent,gun,physobj),time).
  218
  219 /*   if(happens(shoot(Agent, Gun, Physobj), Time),
  220          (happens(shootDamage(Agent, Gun, Physobj), Time);happens(shootDestroy(Agent, Gun, Physobj), Time))).
  221 */
  222
  223 /*  happens(shootDamage(ShootDamage_Param, A, ShootDamage_Ret), Maptime) :-
  224       not(happens(shootDestroy(ShootDamage_Param,
  225                                A,
  226                                ShootDamage_Ret),
  227                   Maptime)),
  228       happens(shoot(ShootDamage_Param, A, ShootDamage_Ret),
  229               Maptime).
  230 */
  231% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:70
  232axiom(happens(shootDamage(ShootDamage_Param, A, ShootDamage_Ret), Maptime),
  233   
  234    [ not(happens(shootDestroy(ShootDamage_Param,
  235                               A,
  236                               ShootDamage_Ret),
  237                  Maptime)),
  238      happens(shoot(ShootDamage_Param, A, ShootDamage_Ret),
  239              Maptime)
  240    ]).
  241
  242 /*  happens(shootDestroy(ShootDestroy_Param, A, ShootDestroy_Ret), Maptime7) :-
  243       not(happens(shootDamage(ShootDestroy_Param,
  244                               A,
  245                               ShootDestroy_Ret),
  246                   Maptime7)),
  247       happens(shoot(ShootDestroy_Param, A, ShootDestroy_Ret),
  248               Maptime7).
  249 */
  250axiom(happens(shootDestroy(ShootDestroy_Param, A, ShootDestroy_Ret), Maptime7),
  251   
  252    [ not(happens(shootDamage(ShootDestroy_Param,
  253                              A,
  254                              ShootDestroy_Ret),
  255                  Maptime7)),
  256      happens(shoot(ShootDestroy_Param, A, ShootDestroy_Ret),
  257              Maptime7)
  258    ]).
  259
  260 /*  not(happens(shoot(Shoot_Param, A, Shoot_Ret), Maptime10)) :-
  261       not(happens(shootDamage(Shoot_Param, A, Shoot_Ret),
  262                   Maptime10)),
  263       not(happens(shootDestroy(Shoot_Param, A, Shoot_Ret),
  264                   Maptime10)).
  265 */
  266axiom(not(happens(shoot(Shoot_Param, A, Shoot_Ret), Maptime10)),
  267   
  268    [ not(happens(shootDamage(Shoot_Param, A, Shoot_Ret),
  269                  Maptime10)),
  270      not(happens(shootDestroy(Shoot_Param, A, Shoot_Ret),
  271                  Maptime10))
  272    ]).
  273
  274
  275% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:72
  276% [agent,gun,bullet,physobj,time]
  277% HoldsAt(Inside(bullet,gun),time) &
  278% Happens(ShootDamage(agent,gun,physobj),time) ->
  279% Happens(Damage(bullet,physobj),time).
  280% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:75
  281axiom(happens(damage(Bullet, Physobj), Time),
  282   
  283    [ holds_at(inside(Bullet, Gun), Time),
  284      happens(shootDamage(Agent, Gun, Physobj), Time)
  285    ]).
  286
  287
  288% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:77
  289% [agent,gun,bullet,physobj,time]
  290% HoldsAt(Inside(bullet,gun),time) &
  291% Happens(ShootDestroy(agent,gun,physobj),time) ->
  292% Happens(Destroy(bullet,physobj),time).
  293% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:80
  294axiom(happens(destroy(Bullet, Physobj), Time),
  295   
  296    [ holds_at(inside(Bullet, Gun), Time),
  297      happens(shootDestroy(Agent, Gun, Physobj), Time)
  298    ]).
  299
  300
  301% From /opt/logicmoo_workspace/packs_sys/small_adventure_games/prolog/ec_planner/ecnet/Gun.e:82
  302%; End of file.