RabbitFarm

2021-01-03

The Weekly Challenge 093 (Prolog Solutions)

Part 1

You are given set of co-ordinates @N. Write a script to count maximum points on a straight line when given co-ordinates plotted on 2-d plane.

Solution


:-initialization(main).

triangle_area(Points, Area):-
    [[X1, Y1], [X2, Y2], [X3, Y3]] = Points,
    Area is (X1 * (Y2 - Y3)) + (X2 * (Y3 - Y1)) + (X3 * (Y1 - Y2)).

collinear_points(Points, CollinearPoints):-
    member(A, Points),
    member(B, Points),
    member(C, Points),
    A \== B, A \== C, B \== C,
    triangle_area([A, B, C], Area),
    Area == 0,
    CollinearPoints = [A, B, C].

main:-
    N = [[5,3], [1,1], [2,2], [3,1], [1,3]],
    collinear_points(N, CollinearPoints),
    write(CollinearPoints), nl,
    halt.

Sample Run


$ gplc ch-1.p
$ ch-1
[[2,2],[3,1],[1,3]]

Notes

Keep in mind that any two points determine a line. Therefore to consider all possible non-trivial lines we need to review all triples of points.

In determining collinearity I calculate the area of a triangle using the triple of points. If the area is zero we know that all the points lay on the same line.

Part 2

You are given a binary tree containing only the numbers 0-9. Write a script to sum all possible paths from root to leaf.

Solution


:-initialization(main).
 
dfs(Node, Graph, [Node|Path]):- 
    dfs(Node, Graph, Path, []).
dfs(_, _, [], _).
dfs(Node, Graph, [AdjNode|Path], Seen) :-
    member(r(Node, Adjacent), Graph),
    member(AdjNode, Adjacent),
    \+ memberchk(AdjNode, Seen),
    dfs(AdjNode, Graph, Path, [Node|Seen]).

sum_paths(Paths, Sum):-
    sum_paths(Paths, 0, Sum).
sum_paths([], Sum, Sum).
sum_paths([H|T], PartialSum, Sum):-
    sum_list(H, ListSum),
    S is PartialSum + ListSum,
    sum_paths(T, S, Sum).

path_lengths([], _).
path_lengths([H|T], [L|Lengths]):-
    length(H, L),
    path_lengths(T, Lengths).

partial_path(_, _, []). 
partial_path(Path, MaxPathLength, [H|T]):-
    length(Path, PathLength),
    length(H, HLength),
    (PathLength < MaxPathLength ; (subtract(Path, H, Remaining), length(Remaining, 0))),
    partial_path(Path, MaxPathLength, T).
partial_path(Path, MaxPathLength, [H|_]):-
    length(Path, PathLength),
    length(H, HLength),
    PathLength =< MaxPathLength,
    subtract(Path, H, Remaining),
    \+ length(Remaining, 0),
    fail.
    
complete_paths(Paths, CompletePaths):-
    path_lengths(Paths, PathLengths),
    max_list(PathLengths, MaxPathLength),
    complete_paths(Paths, Paths, MaxPathLength, [], CompletePaths).
complete_paths([], _, _, CompletePaths, CompletePaths).    
complete_paths([H|T], Paths, MaxPathLength, CompletePathsAccum, CompletePaths):-
    \+ partial_path(H, MaxPathLength, Paths),
    complete_paths(T, Paths, MaxPathLength, [H|CompletePathsAccum], CompletePaths).   
complete_paths([H|T], Paths, MaxPathLength, CompletePathsAccum, CompletePaths):-
    partial_path(H, MaxPathLength, Paths),
    complete_paths(T, Paths, MaxPathLength, CompletePathsAccum, CompletePaths). 
    
main:-
   findall(Path0, dfs(1,[r(1,[2]),r(2,[3,4])], Path0), Paths0),
   complete_paths(Paths0, CompletePaths0),
   sum_paths(CompletePaths0, Paths0Sum),
   write(Paths0Sum), nl,
   findall(Path1, dfs(1,[r(1,[2,3]), r(3,[5,6]), r(2,[4])], Path1), Paths1),
   complete_paths(Paths1, CompletePaths1),
   sum_paths(CompletePaths1, Paths1Sum),
   write(Paths1Sum), nl, halt.

Sample Run


$ gplc ch-2.p 
$ prolog/ch-2
13
26

Notes

The depth first search is pretty idiomatic Prolog and the dfs/3 code was something I grabbed from SO (see references). That code is straightforward enough, it finds all paths in a depth first manner. We are only concerned with the complete root to leaf paths and so a bit of effort goes into filtering out the partial paths. Once that is done the paths are summed and we are done.

The examples used here are from the weekly challenge problem statement and demonstrate the working solution.

References

Challenge 093

Collinear Points

Find all possible paths w/o loops in Graph in Prolog

posted at: 16:36 by: Adam Russell | path: /prolog | permanent link to this entry