1/*********************** operators ****************************************/
    2
    3
    4
    5
    6
    7
    8
    9
   10
   11
   12% method(name,precons,transitions,statics,temps,decomposition)
   13% operator(name,prevail,transitions,cond_transitions)
   14
   15
   16method(
   17 % 1. name
   18      transport2(P,O,D),
   19 % 2. dynamic constraints
   20      [ ],
   21 % 3. list of necessary substate changes
   22      [ sc(package, P, [at(P,O), is_of_sort(P,package)] => 
   23                       [at(P,D), delivered(P)]) ],
   24 % 4. static constraints
   25      [ ne(O,D),in_region(O,R),in_region(D,R)
   26       % list of static predicates that must be instantiated to
   27       % be true. Static preds may also appear in 2. and 3. if
   28       % its clearer that way 
   29       ],
   30
   31 % 5.  temporal  constraints
   32       % list of static predicates before(N1,N2)
   33      [before(1,2),before(2,3)],
   34 % 6. decomposition
   35      [ achieve( ss(package, P,[waiting(P),certified(P)]) ), carry_direct2(P,O,D), deliver(P,D)]
   36 ).
   37
   38method(
   39      transport2(P,O,D),
   40      [ ],
   41      [ sc(package, P, [at(P,O), is_of_sort(P,package)] =>
   42                       [at(P,D), delivered(P)]) ],
   43      [ ne(O,D),ne(R1,R2),is_of_sort(AV,aircraft),
   44        in_region(O,R1),in_region(D,R2),
   45        serves_region(A1,R1),serves_region(A2,R2)
   46       ],
   47      [before(1,2),before(2,3),before(3,4),before(4,5)],
   48      [ achieve( ss(package, P,[waiting(P),certified(P)]) ), 
   49        carry_direct2(P,O,A1), carry_via_ap2(A1,A2,P), 
   50        carry_direct2(P,A2,D), deliver(P,D)]
   51 ).
   52
   53method(
   54   carry_via_ap2(O,D,P),
   55  [ ],
   56  [ sc(package, P, [at(P,O),waiting(P),certified(P)] =>
   57                       [at(P,D),waiting(P),certified(P)]) ],
   58      [ ne(O,D), 
   59%                ne(O,O1), is_of_sort(O1,airport),
   60        is_of_sort(O,airport), is_of_sort(D,airport),
   61        is_of_sort(P,package), is_of_sort(V,aircraft)],
   62 [before(1,3), before(2,3),before(3,4), before(4,5)],
   63  [
   64%       fly(V,O1,O),
   65       commission(V),
   66       achieve(ss(aircraft,V,[at(V,O)])),
   67       load_package(P,V,O),
   68       fly(V,O,D),
   69       unload_package(P,V,D)
   70       ]
   71).
   72
   73% carry in one city
   74method(  
   75  carry_direct2(P,O,D),
   76 [ ],
   77  [ sc(package, P, [at(P,O),waiting(P),certified(P)] => 
   78                       [at(P,D),waiting(P),certified(P)]) ],
   79 [is_of_sort(P,package),
   80       is_of_sort(V,truck),
   81       in_city(O,CY),
   82       in_city(D,CY)
   83       ],
   84 [before(1,2), before(2,3), before(3,4),before(4,5)
   85       ],
   86 [   %  achieve(ss(truck,V,[moveable(V), busy(V)])),
   87       commission(V),
   88       achieve(ss(truck,V,[at(V,O)])),
   89       load_package(P,V,O),
   90       move2(V,O,D,local_roads),
   91       unload_package(P,V,D)
   92       ]
   93).
   94
   95% carry between two cities by traincar
   96method(
   97  carry_direct2(P,O,D),
   98 [ ],
   99  [ sc(package, P, [at(P,O),waiting(P),certified(P)] => 
  100                       [at(P,D),waiting(P),certified(P)]) ],
  101 [is_of_sort(P,package),
  102       is_of_sort(V,traincar),
  103       is_of_sort(Train,train),
  104       connects(R,O,D),
  105       rv_compatible(R,traincar),
  106       route_available(R)
  107       ],
  108 [before(1,2), before(2,3), before(3,4),before(4,5),
  109       before(5,6),before(6,7),before(7,8) ],
  110 [     commission(V),
  111       achieve(ss(train,Train,[at(Train,O),attached(Train,V)])),
  112       load_package(P,V,O),
  113       pull_traincar(Train,V,O,D,R),
  114       detach_traincar(Train,V,D),
  115       unload_package(P,V,D)
  116       ]
  117).
  118
  119% carry between two cities by truck
  120method(
  121  carry_direct2(P,O,D),
  122 [ ],
  123  [ sc(package, P, [at(P,O),waiting(P),certified(P)] => 
  124                       [at(P,D),waiting(P),certified(P)]) ],
  125 [is_of_sort(P,package),
  126       is_of_sort(V,truck),
  127       in_city(O,CY),
  128       in_city(D,CY1),
  129       ne(CY,CY1),
  130       connects(R,CY,CY1),
  131       is_of_sort(R,road_route),
  132       route_available(R)
  133       ],
  134 [before(1,2), before(2,3), before(3,4),before(4,5) ],
  135 [   %  achieve(ss(truck,V,[moveable(V), busy(V)])),
  136       commission(V),
  137       achieve(ss(truck,V,[at(V,O)])),
  138       load_package(P,V,O),
  139       move2(V,O,D,R),
  140       unload_package(P,V,D)
  141       ]
  142).
  143
  144method(
  145  move_traincar2(V, O, L, R2),
  146 [ ],
  147         [sc(traincar,V,[at(V,O) ]
  148            =>[at(V,L)] )],
  149 [is_of_sort(V,traincar),
  150       connects(R2,O,L),
  151       is_of_sort(R2,rail_route),
  152       is_of_sort(Train,train) ],
  153 [before(1,2), before(2,3), before(3,4),before(4,5) ],
  154 [   achieve(ss(train,Train,[at(Train,O)])),
  155          attach_traincar(Train,V,O),
  156          pull_traincar(Train,V,O,L,R2),
  157          detach_traincar(Train,V,L) ]
  158).
  159
  160/* getting docs ready */
  161 operator( pay_fees(P),
  162      [],
  163      [sc(package,P,[uncertified(P)]
  164      =>[waiting(P),certified(P)])],
  165      [ ]).
  166
  167operator(fly(A,D1,D2),
  168      [ ],
  169      [sc(aircraft,A,[at(A,D1)]
  170            =>[at(A,D2)] )],
  171         [sc(package,X,[loaded(X,A),certified(X),at(X,D1)]
  172            => [loaded(X,A),certified(X),at(X,D2)])  ]
  173).
  174
  175
  176%move2 truck
  177operator( move2(V, O, L, R), 
  178        [ ],
  179         [sc(truck,V,[at(V,O),
  180             is_of_sort(R,road_route),
  181             moveable(V),
  182             in_city(O,City),
  183             in_city(L,City1),
  184             ne(City,City1),
  185             connects(R,City,City1)]
  186            =>[at(V,L)] )],
  187         [sc(package,X,[loaded(X,V),certified(X),at(X,O)] 
  188            => [loaded(X,V),certified(X),at(X,L)])  ]
  189).
  190
  191%move2 truck inside city
  192operator( move2(V, O, L, local_roads), 
  193         [],
  194         [sc(truck,V,[at(V,O),
  195             moveable(V),
  196             in_city(O,City),
  197             in_city(L,City)]
  198            =>[at(V,L)]  )],
  199         [ sc(package,X,[loaded(X,V),certified(X),at(X,O)] 
  200            =>[loaded(X,V),certified(X),at(X,L)])   ]
  201).
  202
  203%move2 traincar
  204operator( pull_traincar(Train,V1, O, L, Rt), 
  205         [  ],
  206         [ sc(train,Train,[at(Train,O),
  207             attached(Train,V1),
  208             moveable(Train),
  209             connects(Rt,O,L),
  210             is_of_sort(Rt,rail_route)]
  211            =>[at(Train,L),attached(Train,V1)] ),
  212           sc(traincar,V1,[at(V1,O),attached(V1,Train)]
  213            =>[at(V1,L),attached(V1,Train)]) ],
  214         [sc(package,P,[loaded(P,V1),certified(P),at(P,O)]
  215            =>[loaded(P,V1),certified(P),at(P,L)]) ]
  216).
  217
  218operator( move_train(V, O, L, Rt),
  219         [ ],
  220          [sc(train,V,[at(V,O),unattached(V),
  221             moveable(V),available(V),
  222             connects(Rt,O,L),
  223             is_of_sort(Rt,rail_route)]
  224            =>[at(V,L),unattached(V),moveable(V),available(V)] )],
  225       [ ]
  226).
  227
  228operator(attach_traincar(Train,V,O),
  229     [  ],
  230     [sc(train, Train, [at(Train,O),moveable(Train),available(Train),unattached(Train)]
  231        =>[at(Train,O),attached(Train,V),moveable(Train),busy(Train)] ),
  232     sc(traincar, V, [at(V,O),unattached(V)]
  233        =>[at(V,O),attached(V,Train)] ) ],
  234     [ ]
  235).
  236
  237operator(detach_traincar(Train,V,O),
  238     [ ],
  239     [sc(train, Train, [attached(Train,V),moveable(Train),busy(Train)]
  240        =>[unattached(Train),moveable(Train),available(Train)] ),
  241     sc(traincar, V, [attached(V,Train)]
  242        =>[unattached(V)] ) ],
  243     [ ]
  244).
  245
  246operator(commission(V),
  247      [ ],
  248      [sc(vehicle, V,[moveable(V),available(V)] =>[moveable(V), busy(V)])],
  249      [ ]).
  250
  251         
  252
  253operator( load_package(P,V,L),
  254   [ss(vehicle,V, [at(V,L),moveable(V),busy(V)])],
  255   [sc(package, P, [at(P,L),waiting(P),certified(P)]=>
  256      [at(P,L),loaded(P,V),certified(P)])],
  257   []
  258).
  259
  260operator( unload_package(P,V,L),
  261 [],
  262 [sc(package, P, [at(P,L),loaded(P,V),certified(P)]=>[at(P,L),waiting(P),certified(P)]
  263),
  264 sc(vehicle,V, [at(V,L), moveable(V), busy(V)] => [at(V,L),moveable(V),available(V)])
  265],
  266 []
  267 ).
  268
  269
  270operator( deliver(P,L),
  271        [],
  272        [sc(package, P, [at(P,L),waiting(P),certified(P)]=>
  273          [at(P,L),delivered(P)] )],
  274        []
  275)