Compare commits

..

2 Commits

Author SHA1 Message Date
Spencer Killen 980a80d6af
a 2023-03-28 03:40:05 +00:00
Spencer Killen 6b716c75a1
a 2023-03-28 03:36:00 +00:00
5 changed files with 228 additions and 6 deletions

24
TODO.md Normal file
View File

@ -0,0 +1,24 @@
- Demo doing graph colouring program
- Explain graph colouring
- Goal is to learn how to learn
- Manual too
- Small examples
- Hypothesize and test
- No one "right" way to model a problem
- Less complicated is generally better
- First: direct example (color_prim.lp)
- Show basic grounding
- Uncomment vertex: we're missing some
- Uncomment arc to make the graph symmetric (undirected)
- Show basic solving and disjunctive rule
- Ground it first.
- We have dupes
- Ferry problem
- Explain time
CLPFD

View File

@ -1,6 +0,0 @@
% Graph colouring
%#show color/2.
%{ color(X,1..n) } = 1 :- vertex(X).
%:- arc(X,Y), color(X,C), color(Y,C).

27
asp/clp.pl Normal file
View File

@ -0,0 +1,27 @@
:- use_module(library(clpfd)).
vertex(1).
vertex(2).
vertex(3).
link(1, 2).
link(1, 3).
link(2, 3).
arc(X, Y) :- link(X, Y).
arc(X, Y) :- link(Y, X).
coloring(Colors) :-
findall(V, vertex(V), Vertices),
length(Vertices, N),
same_length(Colors, Vertices),
Colors ins 0..N, % At most N different colors
maplist(constrain1(Vertices, Colors), Vertices, Colors),
sum(Colors, #=, Sum),
labeling([min(Sum)], [Sum | Colors]).
constrain1(Vertices, Colors, Vertex, Color) :-
maplist(constrain2(Vertex, Color), Vertices, Colors).
constrain2(V1, C1, V2, C2) :-
arc(V1, V2), !,
C1 #\= C2.
constrain2(_, _, _, _).

33
asp/color.lp Normal file
View File

@ -0,0 +1,33 @@
arc(1, (2; 3)).
arc(2, 3).
% Collect the vertices
vertex(X) :- arc(X, _).
% Symmetry (undirected graph)
arc(X, Y) :- arc(Y, X).
% Representation 1:
% #show red/1. #show green/1. #show blue/1.
% red(Vertex), green(Vertex), blue(Vertex) :- vertex(Vertex).
% % Remove the dupes
% :- red(V1), red(V2), V1 != V2.
% :- green(V1), green(V2), V1 != V2.
% :- blue(V1), blue(V2), V1 != V2.
% Remove the adjacent edges with same color
% :- arc(X, Y), red(X), red(Y).
% :- arc(X, Y), green(X), green(Y).
% :- arc(X, Y), blue(X), blue(Y).
% Representation 2:
% #const n = 6.
% #show color/2.
% { color(X,1..n) } = 1 :- vertex(X).
% :- arc(X,Y), color(X,C), color(Y,C).

144
asp/ferry.lp Normal file
View File

@ -0,0 +1,144 @@
% Initially, there are cars at various locations, and there is a
% ferry at some location. The ferry can only transport one car at
% a time and the goal is to transport all cars to their
% destinations. No paralell actions are allowed.
#show board/3.
#show move/4.
#show unboard/3.
%#show at/3.
%#show in/3.
%#show moving/3.
time(0..steps).
% Clingo processes "safe programs": any variable occuring in a
% negative literal of rule r must appear in a positive atom in the body of r.
%
% There is nothing wrong to use domains predicates. One may first write
% these predicates and then comment the unnessary ones out (as shown).
% Nothing wrong to leave them there.
% Not all of them can be removed, specially when there is a possibility
% a variable can be instantiated (during grounding) to something unintended.
% You may discover this during debugging using the "#show" diretive.
% actions
{board(Car,Loc,T)} :-
car(Car),
% location(Loc), time(T),
empty(ferry,T),
at(Car,Loc,T),
at(ferry,Loc,T),
not moving(ferry,Loc,T),
not goal(T).
{unboard(Car,Loc,T)} :-
car(Car),
% location(Loc), time(T),
in(ferry,Car,T),
at(ferry,Loc,T),
not moving(ferry,Loc,T),
not goal(T).
{move(ferry,From,To,T)} :-
% car(Car),location(From), time(T),
location(To),
at(ferry,From,T),
From != To,
not goal(T).
moving(ferry,From,T):- % irrelevant of where ferry moves to
% location(From),location(Loc), time(T),
at(ferry,From,T),
move(ferry,From,Loc,T).
% Below is the wrong code to define empty: it says if there exists
% a Car not in ferry, then ferry is empty.
%
% empty(ferry,T):-
% car(Car), time(T),
% not in(ferry,Car,T).
empty(ferry,T):- time(T), not occupied(ferry,T).
occupied(ferry,T) :- in(_,_,T).
%fluents
in(ferry,Car,T+1):- %an action causes a property to hold
% car(Car), location(Loc), time(T),
at(ferry,Loc,T),
board(Car,Loc,T).
in(ferry,Car,T+1):-
% car(Car),
time(T),
in(ferry,Car,T),
not affected0(Car,T).
affected0(Car,T) :-
% time(T), car(Car), location(Loc),
unboard(Car,Loc,T).
% !!! Cannot replace the above by below - it says that
% Car is in ferry at T+1 if at T there is a location Loc
% s.t. Car is not unboarded - not intended!
%
% in(ferry,Car,T+1):-
% car(Car), time(T),
% in(ferry,Car,T),
% not unboard(Car,Loc,T).
at(ferry,Loc,T+1):-
% car(Car), location(Loc), time(T),
at(ferry,Loc,T),
board(Car,Loc,T).
at(ferry,Loc,T+1):-
% car(Car), location(Loc), time(T),
at(ferry,Loc,T),
unboard(Car,Loc,T).
at(ferry,Loc,T+1):-
% location(Loc),
time(T),
at(ferry,Loc,T), %if we don't have tis line, what could happen?
%A: ferry can be everywhere
not moving(ferry,Loc,T).
at(ferry,To,T+1):-
% location(To),location(From),
time(T),
at(ferry,From,T),
move(ferry,From,To,T).
at(Car,Loc,T+1):-
car(Car), % not commented out - don't want Car instantied to ferry
% location(Loc), time(T),
unboard(Car,Loc,T).
at(Car,Loc,T+1):- %frame axiom
car(Car), location(Loc), time(T),
at(Car,Loc,T),
not board(Car,Loc,T).
goal(T+1):- time(T), goal(T).
%once goal is achieved, goal(T) is true for all T > k.
goal :- time(T), goal(T).
:- not goal.
% The code above works for the input file, ferryIn0.lp and ferryIn1.lp,
% but not ferryIn2.lp.
%
% Discover what is wrong. Consider adding the following constraints:
%
% 1. ferry cannot be moved to two different locations at the same time
% 2. it's not possible to board different cars at the same time and same location.