124
128
129office([central|L]) :- setof(station(X), member(X,[1,6,11,7,9,12,13,16]), L).
130corridor(L) :- setof(station(X),member(X,[2,3,4,5,8,14,10,15]),L).
131location(L) :- office(L1), corridor(L2), append(L1,L2,L).
132
133direction([north,south,west,east]).
134degree([90,180,-90,180,-180]).
135priority([1,2,3,4,5]).
136
138anyLocation(A) :-
139 location(P),
140 setof(E, betweenPlaces(E), B),
141 append(P,B,A).
142betweenLocation(P) :- 143 location(X1),
144 location(X2),
145 X1\=X2,
146 P = between(X1,X2).
147
151
153cache(direction).
154cache(robotLocation).
155
157
161
163fun_fluent(direction).
164causes_val(turnLeft, direction, north, direction=east).
165causes_val(turnLeft, direction, west, direction=north).
166causes_val(turnLeft, direction, south, direction=west).
167causes_val(turnLeft, direction, east, direction=south).
168
169causes_val(turnRight, direction, north, direction=west).
170causes_val(turnRight, direction, west, direction=south).
171causes_val(turnRight, direction, south, direction=east).
172causes_val(turnRight, direction, east, direction=north).
173
174causes_val(turnAround, direction, north, direction=south).
175causes_val(turnAround, direction, west, direction=east).
176causes_val(turnAround, direction, south, direction=north).
177causes_val(turnAround, direction, east, direction=west).
178
179causes_val(turn(D), direction, V, rotation(direction,V,D)).
180causes_val(startLocalization, direction, north, true).
181causes_val(setLocation(_,D), direction, D, true).
182
184fun_fluent(robotLocation).
185causes_val(goNext, robotLocation, P,
186 and(getEdge(robotLocation,P2,direction,currentMap),
187 P=between(robotLocation,P2)) ).
188causes_val(reachDest, robotLocation, P, robotLocation=between(_,P)).
189causes_val(turnAround, robotLocation, between(P2,P1), robotLocation=between(P1,P2)).
190causes_val(setLocation(L,_), robotLocation, L, true).
191causes_val(startLocalization, robotLocation, station(2), true).
192
194fun_fluent(robotLastPlace).
195causes_val(goNext, robotLastPlace, P, P=robotLocation).
196
198fun_fluent(robotDestination).
199causes_val(goNext,robotDestination,P,getEdge(robotLocation,P,direction,currentMap)).
200
202rel_fluent(blocked(_,_)).
203causes_true(getStuck, blocked(P1,P2), robotLocation=between(P1,P2)).
204causes_true(getStuck, blocked(P1,P2), robotLocation=between(P2,P1)).
205causes_false(clearRoute(P1,P2), blocked(P1,P2), true).
206causes_false(clearRoute(P1,P2), blocked(P2,P1), true).
207
208
210rel_fluent(talking).
211causes_true(talk, talking, true).
212causes_false(shutup, talking, true).
213
214
215
219
221fun_fluent(robotState).
222causes_val(goNext, robotState, moving, true).
223causes_val(searchPath, robotState, moving, true).
224causes_val(reachDest, robotState, reached, robotState=moving).
225causes_val(stop_abnormally, robotState, lost, true).
226causes_val(freezeRobot, robotState, frozen, true).
227causes_val(resetRobot, robotState, idle, true).
228causes_val(dropOff, robotState, waitingPush, true).
229causes_val(pushGo, robotState, readyGo, robotState=waitingPush).
230causes_val(getStuck, robotState, stuck, true).
231
233rel_fluent(robotLost).
234causes_true(stop_abnormally, robotLost, true).
235causes_false(setLocation(_,_), robotLost, true).
236
237
241
243rel_fluent(startOrder).
244
246fun_fluent(sender).
247
249fun_fluent(recipient).
250causes_val(dropOff, recipient, unknown, holdingShip).
251senses(readRecipient, recipient).
252
254rel_fluent(holdingShip).
255causes_true(pickUp, holdingShip, serviceAccepted(robotLocation)).
256causes_false(dropOff, holdingShip, true).
257
259rel_fluent(askedService(_)).
260causes_true(orderShipment(C,_), askedService(C), true).
261causes_false(ackOrder(C), askedService(C), true).
262causes_false(declineOrder(C), askedService(C), true).
263
265fun_fluent(orderPrio(_)).
266causes_val(orderShipment(C,P), orderPrio(C), P, true).
267
269rel_fluent(serviceAccepted(_)).
270causes_false(declineOrder(C), serviceAccepted(C), true).
271causes_true(ackOrder(C), serviceAccepted(C), true).
272causes_false(pickUp, serviceAccepted(C), robotLocation=C).
273
275rel_fluent(suspended(_)).
276causes_true(suspend(C), suspended(C), true).
277causes_false(enable(C), suspended(C), true).
278
280fun_fluent(mailBox(_)).
281causes_val(emptyMailBoxes, mailBox(C), 0, customer(C)).
282causes_val(dropOff, mailBox(C), N, and(robotLocation=central,
283 and(recipient=C,
284 N is mailBox(C)+1)) ).
286rel_fluent(mailBoxFull(_)).
287
289rel_fluent(inOffice(_)).
290causes_true(in(C), inOffice(C), true).
291causes_false(out(C), inOffice(C), true).
292senses(senseDoor(C), inOffice(C)).
293
294
295
296
300prim_action(startLocalization).
301poss(startLocalization, true).
302
303prim_action(addNode(N)) :- domain(N,location).
304poss(addNode(_), robotLost).
305
306prim_action(addEdge(_)).
307poss(addEdge(_), robotLost).
308
309prim_action(addNEdge(_)).
310poss(addNEdge(_), robotLost).
311
312prim_action(addCounter).
313poss(addCounter, robotLost).
314
315prim_action(setCurrentMap(_)).
316poss(setCurrentMap(_), robotLost).
317
318fun_fluent(counterStations).
319causes_val(startLocalization, counterStations, 2, true).
320causes_val(addCounter, counterStations, X, X is counterStations+1).
321
322fun_fluent(currentMap).
323causes_val(startLocalization, currentMap,
324 graph([station(1),station(2)],[edge(station(1),station(2),south),
325 edge(station(2),station(1),north)],[]), true).
326causes_val(setCurrentMap(G), currentMap, G, true).
327causes_val(A, currentMap, G,
328 and(neg(A=startLocalization),
329 and(neg(some(g,A=setCurrentMap(g))), realWorldGraph(G))) ).
330
331
332causes_val(addNode(N), currentMap, NewMap, add_node(N,currentMap,NewMap)).
333causes_val(addEdge(E), currentMap, NewMap, add_edge(E,currentMap,NewMap)).
334causes_val(addNEdge(E), currentMap, NewMap, add_nedge(E,currentMap,NewMap)).
335
336rel_fluent(stationVisited(_)).
337causes_true(reachDest, stationVisited(S), robotDestination=S).
338causes_false(startLocalization, stationVisited(S), location(S)).
339
340
342prim_action(senseLine).
343senses(senseLine, lineBelow).
344poss(senseLine, true).
345rel_fluent(lineBelow).
346
347proc(localize,
348 [startLocalization,
349 addCounter, 350 351 while(neg(some(l,some(d,uniquePlace(l,d)))), localizeOneStep),
352 pi(loc,
353 pi(deg,
354 pi(dir,
355 [?(uniquePlace(loc,deg)),
356 ?(rotation(direction,dir,deg)),
357 setLocation(loc,dir)
358 ]
359 )))
360 ]
361).
362
365proc(uniquePlace(Loc,Deg),
366 some(realWorld,
367 and(realWorldGraph(realWorld),
368 uniqueLocation(currentMap,realWorld, robotLocation, Loc, Deg)
369 )
370 )
371).
372
373proc(localizeOneStep,
374 [discoverStation,
375 pi(station,
376 pi(path,
377 [?(and(getNode(station,currentMap),neg(stationVisited(station)))),
378 ?(path_graph_short(robotLocation,station,currentMap,10,path)),
379 pi(x, pi(restpath, [?(path=[x|restpath]), traversePath(restpath)]))
380 ])),
381 cleanMap]
382).
383
384proc(discoverStation,
385 [turn(-90),
386 senseLine,
387 if(lineBelow,addStation,addNonStation),
388 turn(90),
389 390 turn(90),
391 senseLine,
392 if(lineBelow,addStation,addNonStation),
393 turn(-90),
394 395 moveFwd,
396 senseLine,
397 if(lineBelow,addStation,addNonStation),
398 moveBack]
399).
400
401
402proc(addNonStation,
403 pi(reverseDir,
404 [addNEdge(edge(robotLocation,_,direction)),
405 ?(rotation(direction,reverseDir,180)),
406 addNEdge(edge(_,robotLocation,reverseDir))]
407 )
408).
409
410proc(addStation,
411 pi(c,
412 pi(reverseDir,
413 [?(c=counterStations),
414 addNode(station(c)),
415 addEdge(edge(robotLocation,station(c),direction)),
416 ?(rotation(direction,reverseDir,180)),
417 addEdge(edge(station(c),robotLocation,reverseDir)),
418 addCounter]
419 ))
420).
421
422proc(cleanMap,
423 pi(realWorld,
424 pi(newMap, [?(realWorldGraph(realWorld)),
425 ?(cleanGraph(currentMap, realWorld, newMap)),
426 setCurrentMap(newMap)]
427 ))
428).
429
430
431
432
433
434
437uniqueLocation(G1, G2, NodeG1, Loc, Deg) :-
438 439 findall((M,D), sub_graph_rot(G2, G1, M, D), [(Map,Deg)]),
440 member((Loc,NodeG1), Map).
441
442
444cleanGraph(G1, G2, GNew) :-
445 446 findall(M, D^sub_graph_rot(G2, G1, M, D), LMaps),
447 setof((Node1,Node2), (getNode(Node1,G1), 448 getNode(Node2,G1),
449 Node1\=Node2,
450 \+ not_equal_nodes(Node1,Node2,LMaps)), LEqualNodes),
451 remove_equal_nodes(LEqualNodes, G1, GNew).
452cleanGraph(G1,_,G1).
453
454
457not_equal_nodes(Node1, Node2, LMaps) :-
458 member(Map, LMaps),
459 member((MapNode1,Node1), Map),
460 member((MapNode2,Node2), Map),
461 MapNode1\=MapNode2.
462
463
464remove_equal_nodes([], G, G).
465remove_equal_nodes([(N1,N2)|Tail], G, GNew) :-
466 getNode(N1,G),getNode(N2,G),!,
467 combine_nodes(N1,N2,G,GNew2),
468 remove_equal_nodes(Tail, GNew2, GNew).
469remove_equal_nodes([_|Tail], G, GNew) :-
470 remove_equal_nodes(Tail, G, GNew).
471
472
473
474
475
476
477
478
482
483
487
489prim_action(ackOrder(C)) :- domain(C,office).
490poss(ackOrder(C), neg(serviceAccepted(C)) ).
491
493prim_action(declineOrder(C)) :- domain(C,office).
494poss(declineOrder(_), true).
495
497prim_action(suspend(C)) :- domain(C,office).
498poss(suspend(C), and(neg(inOffice(C)), serviceAccepted(C)) ).
499
501prim_action(enable(C)) :- domain(C,office).
502poss(enable(_), true).
503
504
505
509
510
512prim_action(pickUp).
513poss(pickUp, robotState=readyGo).
514
516prim_action(dropOff).
517poss(dropOff, and(robotState=frozen,
518 or(inOffice(robotLocation), and(robotLocation=central,
519 mailBox(recipient)<3))
520 )
521).
522
524prim_action(resetRobot).
525poss(resetRobot, true).
526
528prim_action(goNext).
529poss(goNext, or(some(a,some(b,robotLocation=between(a,b))),
530 some(next, and(getEdge(robotLocation,next,direction,currentMap),
531 neg(blocked(robotLocation,next))))) ).
532
534prim_action(moveBack).
535poss(moveBack, true).
536
537prim_action(moveFwd).
538poss(moveFwd, true).
539
541prim_action(turnLeft).
542poss(turnLeft, isEdgeLeft).
543
545prim_action(turnRight).
546poss(turnRight, isEdgeRight).
547
549prim_action(turn(D)) :- domain(D,degree).
550poss(turn(D), or(D=90,or(D=180,or(-90=D,-180=D))) ).
551
553prim_action(turnAround).
554poss(turnAround, and(neg(isEdgeLeft), neg(isEdgeRight)) ).
555
557prim_action(setLocation(L,D)) :- domain(L, location), domain(D, direction).
558poss(setLocation(_,_), robotLost).
559
561prim_action(freezeRobot).
562poss(freezeRobot, true).
563
565prim_action(readRecipient).
566poss(readRecipient, holdingShip).
567
569prim_action(senseDoor(C)) :- domain(C,office).
570poss(senseDoor(C), robotLocation=C).
571
573prim_action(say(_)).
574poss(say(_), true).
575
577prim_action(ring).
578poss(ring, true).
579
580
584exog_action(debug).
585
587exog_action(emptyMailBoxes).
588
590exog_action(stop_abnormally).
591
593exog_action(reachDest).
594
596exog_action(pushGo).
597
599exog_action(getStuck).
600
602exog_action(clearRoute(P1,P2)) :- domain(P1, location), domain(P2, location).
603
605exog_action(in(C)) :- domain(C, office).
606exog_action(out(C)) :- domain(C, office).
607
609exog_action(orderShipment(Sender,Prio)) :-
610 domain(Sender, office),
611 domain(Prio, priority).
612
614exog_action(talk).
615exog_action(shutup).
616
617
618
623
625
627initially(robotLocation, central).
629initially(direction, east).
630
631
633initially(robotState, idle).
634initially(robotLost, false).
635initially(holdingShip, false).
636initially(talking, true).
637
638initially(startOrder,false).
643initially(inOffice(central), true).
644
646initially(askedService(station(6)), true).
647initially(orderPrio(station(6)), 12).
648initially(askedService(C), false) :-
649 domain(C,office),
650 \+ initially(askedService(C), true).
651
653initially(mailBox(station(13)), 3).
654initially(mailBox(C), 0) :-
655 domain(C, office), C\=13.
656
658initially(suspended(C), false) :- domain(C,office).
659initially(serviceAccepted(C), false) :- domain(C,office).
660
662initially(recipient,unknown).
663
664
665initially(currentMap, G) :- realWorldGraph(G).
666initially(counterStations,5).
667
668
676
677
678
679
680
684
688proc(bestCustToServe(C),
689 and(serviceAccepted(C),
690 and(neg(suspended(C)),
691 neg(some(c,and(serviceAccepted(c),
692 and(neg(suspended(c)), orderPrio(c)>orderPrio(C)))))
693 ))).
694
695
696
698proc(isEdgeLeft,
699 some(dir, some(x,
700 and(rotation(direction,dir,-90),
701 getEdge(robotLocation,x,dir,currentMap))))
702).
703
704proc(isEdgeRight,
705 some(dir, some(x,
706 and(rotation(direction,dir,90),
707 getEdge(robotLocation,x,dir,currentMap))))
708).
709
710
711
715
718proc(minimization(E,C,Max), minimize(E,C,Max,0)).
719proc(minimize(E,C,Max,N),
720 wndet(search([exec(E,N),?(C)]),
721 [?(N<Max),pi(n2,[?(n2 is N+1), minimize(E,C,Max,n2)])])).
722
724proc(exec(E,N),
725 wndet(?(N=0), [E,pi(n2,[?(n2 is N-1),exec(E,n2)])]) ).
726
728proc(handleNewOrder(C), wndet(ackOrder(C), declineOrder(C)) ).
729
732proc(nextStation(Dest,Next),
733 ?(path_graph_short(robotLocation,Dest,currentMap,10,[_,Next|_])) ).
734
736proc(goToLocation(Loc),
737 pi(path,
738 [?(path_graph_short(robotLocation,Loc,currentMap,10,path)) ,
739 pi(x, pi(restpath, [?(path=[x|restpath]), traversePath(restpath)]))
740 ])
741).
742
744proc(traversePath(Path),
745 pi(next,
746 pi(rest, [?(Path=[next|rest]),
747 turnToAim(next),
748 goNext,
749 sim(reachDest),
750 if(rest=[], ?(true), traversePath(rest))
751 ]
752 ))
753).
754
756proc(turnToAim(Next),
757 [star(ndet(turnLeft,ndet(turnRight,turnAround)),2),
758 ?(getEdge(robotLocation,Next,direction,currentMap))
759 ]
760).
761
762
772proc(serve,
773pi(c,[wndet(?(and(holdingShip,c=recipient)), ?(bestCustToServe(c))),
774 goToLocation(c),
775 commit,
776 senseDoor(c),
777 branch(inOffice(c)),
778 wndet(search(service), wndet(suspend(c), [goToLocation(central), service])),
779 resetRobot]
780)).
781
783proc(service, [freezeRobot, dropOff, sim(pushGo), pickUp]).
784
786proc(recover_position,
787 [say('I got lost! I will try to find where I am...'),
788 searchPath, 789 localize
790 ]
791).
792
793prim_action(searchPath).
794poss(searchPath, robotLost).
795
797manual_localization(Location, Direction, M) :-
798 (Direction = 1 -> MDir=' going up.' ; MDir=' going down.'),
799 concat_atom(['I got lost heading from waystation ', Location,
800 ' while ', MDir,
801 '.. Please position me between waystations in ',
802 ' the correct direction, and type any key when ready.'],M).
803
807
808proc(mainControl(2), [prioritized_interrupts(
809 [interrupt(or(robotState = moving, robotState = waitingPush),
810 wait),
811 interrupt(true, localize)]
812 )]
813).
814
815
816proc(mainControl(1), [prioritized_interrupts(
817 [interrupt(robotState = lost,
818 [resetRobot, recover_position, goNext]),
819 interrupt(n, askedService(n),
820 handleNewOrder(n)),
821 interrupt(or(robotState = moving, robotState = waitingPush),
822 wait),
823 interrupt(robotState = stuck,
824 [resetRobot,
825 abort(startOrder),
826 moveBack,
827 turnAround,
828 goNext,
829 resetRobot]),
830 interrupt(c, and(serviceAccepted(c), suspended(c)),
831 declineOrder(c)),
832 interrupt(holdingShip,
833 [wndet(?(neg(recipient=unknown)), readRecipient),
834 search([gexec(startOrder,searchc(serve))])]),
835 interrupt(c, and(robotState = idle, serviceAccepted(c)),
836 [say(['Trying to serve ',c]),
837 wndet(search([gexec(startOrder, searchc(serve))]),
838 [say(['Sorry it is not safe to serve ',c]),declineOrder(c)])
839 ]),
840 interrupt(and(neg(robotLocation=central), neg(holdingShip)),
841 [say('Wrapping up to central office...'),
842 search(pi(c,[nextStation(central,c), turnToAim(c), goNext])),
843 resetRobot]),
844 interrupt(true, [say('Waiting at central station....'), wait])]
845 )]).
846
847
848
852
857
865
867actionNum(turnAround, 1).
868actionNum(turnLeft, 2).
869actionNum(turnRight, 3).
870actionNum(pickUp, 4).
871actionNum(dropOff, 5).
872actionNum(goNext, 6).
873actionNum(moveBack, 7).
874actionNum(moveFwd, 8).
875actionNum(freezeRobot, 9).
877actionNum(resetRobot, 11).
878actionNum(ring, 12).
879actionNum(senseLine, 13).
880actionNum(searchPath, 14).
881
883actionNum(reachDest, 20).
884actionNum(stop_abnormally, 21).
885actionNum(pushGo, 22).
886actionNum(getStuck, 23).
887
888
889
893
897
902
903
904
905
906
907
911
913
914
915
916
920
923sub_graph_rot(G1, G2, Map, D) :-
924 member(D,[0,90,180,270]),
925 rotate_graph(G2, D, RG2),
926 sub_graph(G1,RG2,Map).
927
929rotate_graph(graph(Nodes, Edges), D, graph(RNodes, REdges)) :-
930 rotate_graph(graph(Nodes, Edges,[]), D, graph(RNodes, REdges,[])).
931rotate_graph(graph(Nodes, Edges, NEdges), D, graph(Nodes, REdges,RNEdges)) :-
932 maplist(rotate_edge(D),Edges,REdges),
933 maplist(rotate_edge(D),NEdges,RNEdges).
934
936rotate_edge(Degrees, edge(S,D,O), edge(S,D,RO)) :-
937 rotation(O, RO, Degrees).
938
940rotation(X, Y, D) :-
941 rotate_clock(X,Y,DC),
942 (D=DC ; D is (360-DC)*(-1)).
943
944rotate_clock(X, X, 0).
945rotate_clock(X, Y, 90) :-
946 rot(X, Y, 90).
947rotate_clock(X, Y, 180) :-
948 rot(X, Z, 90),
949 rot(Z, Y, 90).
950rotate_clock(X, Y, 270) :-
951 rot(X, Z, 90),
952 rot(Z, W, 90),
953 rot(W, Y, 90).
954
955rot(north,east,90).
956rot(east,south,90).
957rot(south,west,90).
958rot(west,north,90).
959
960
961
965
967nodes(circle,L) :- location(L).
968edge(circle,X,Y,D) :- edge1(circle,X,Y,D).
969edge(circle,X,Y,D) :- rotation(D2,D,180), edge1(circle,Y,X,D2).
970
971edge1(circle, central, station(2), north).
972edge1(circle, station(2), station(3), east).
973edge1(circle, station(3), station(4), south).
974edge1(circle, station(4), station(5), south).
975edge1(circle, central, station(15), south).
976edge1(circle, station(15), station(5), east).
977
978edge1(circle, station(2), station(6), west).
979
980edge1(circle, central, station(8), west).
981edge1(circle, station(8), station(7), north).
982edge1(circle, station(8), station(9), south).
983
984edge1(circle, station(3), station(10), east).
985edge1(circle, station(10), station(11), east).
986edge1(circle, station(10), station(14), south).
987edge1(circle, station(14), station(13), east).
988edge1(circle, station(13), station(12), north).
989edge1(circle, station(13), station(16), south).
990edge1(circle, station(16), station(5), west).
991
992
1018
1019
1020map_graph(Id, graph(Nodes, Edges)) :-
1021 nodes(Id, Nodes),
1022 setof(edge(S,D,O),O2^(edge(Id,S,D,O) ;
1023 edge(Id,D,S,O2), rotation(O2,O,180)),Edges).
1024
1025realWorldGraph(G) :- map_graph(circle, G).
1026
1027
1028
1032
1036connected(Id, between(P1,P2),P,D):- !,
1037 ( connected(Id, P1,P2,D), P=P2
1038 ;
1039 connected(Id, P2,P1,D),P=P1
1040 ).
1041connected(Id, X, Y, west) :- edge(Id, X, Y, west) ; edge(Id, Y, X, east).
1042connected(Id, X, Y, east) :- edge(Id, X, Y, east) ; edge(Id, Y, X, west).
1043connected(Id, X, Y, north):- edge(Id, X, Y, north) ; edge(Id, Y, X, south).
1044connected(Id, X, Y, south):- edge(Id, X, Y, south) ; edge(Id, Y, X, north).
1045
1047connected(Id, C1, C2):- connected(Id, C1, C2, _) ; connected(Id, C2, C1, _).
1048
1049
1052hasLeft(Id, X, D) :- rotation(D, D2, -90), connected(Id, X,_, D2).
1053hasRight(Id, X, D):- rotation(D, D2, 90), connected(Id, X,_, D2).
1054
1055
1057mindist(P1, P2, Dist) :- mindist2(P1,P2,Dist,1).
1058
1059mindist2(P1,P2,Limit,Limit) :- length(Path,Limit), path(P1,P2,Path), !.
1060mindist2(P1,P2,Dist,Limit) :- L2 is Limit+1, mindist2(P1,P2,Dist,L2).
1061
1062
1065
1067path(X, Y, Path) :- path1(X, [Y], [X|Path]).
1068
1069path1(X, [X | Path], [X | Path]).
1070
1071path1(X, [Y | Path1], Path) :-
1072 connected(Y, Z, _),
1073 \+ member(Z, Path1),
1074 path1(X, [Z, Y | Path1], Path).
1075
1077in_path(X, Y, Z) :-
1078 path(X, Y, [Z|_]).
1079
1080
1082path_plan_short(X, Y, G, Limit, P) :- path_plan_short(X,Y,G,0,Limit, P).
1083
1084path_plan_short(X,Y,G,N,_,P) :- path_plan(X,Y,G,N,P), !.
1085path_plan_short(X,Y,G,N,L,P) :-
1086 L\=0,
1087 L2 is L-1, N2 is N+1, path_plan_short(X,Y,G,N2,L2,P).
1088
1089
1091path_plan(X, Y, Id, L, [X|LV]) :-
1092 length(LV, L), 1093 path1_plan(Id, Y, [X|LV]).
1094
1095path1_plan(_, X, [X]).
1096path1_plan(Id, X, [Y | Path1]) :-
1097 edge(Id,Z,Y,_), 1101 Path1=[Z|_],
1102 path1_plan(Id, X, Path1).
1103
1104
1105
1106
1110