Solutions for Session 8

Graphs

  1. all_parents(Graph,Node,ParentList) :-
    	findall(Parent,member(Parent/Node,Graph),ParentList).
    
    Some queries:
    ?- all_parents([a/c,c/d,c/e,b/d,d/e],d,Parents).
    Parents = [c, b] 
    Yes
    ?- all_parents([a/c,c/d,c/e,b/d,d/e],e,Parents).
    Parents = [c, d] 
    Yes
    ?- all_parents([a/c,c/d,c/e,b/d,d/e],b,Parents).
    Parents = []
    
  2. Given a graph and a node, the predicate p writes all the parents of that node to the screen followed by 'end'.
    ?- p([a/c,c/d,c/e,b/d,d/e],b).
    end
    Yes
    
    ?- p([a/c,c/d,c/e,b/d,d/e],d).
    c
    b
    end
    Yes
    
    ?- p([a/c,c/d,c/e,b/d,d/e],e).
    c
    d
    end
    Yes
    
  3. shortest_path(From,To,Graph,ShortestPath):-
            findall(Path,find_path_2(From,To,Graph,Path), Paths),
            Paths = [FirstPath|OtherPaths], % fails if no path exists
            length(FirstPath,L),
            find_shortest(OtherPaths,FirstPath,L,ShortestPath).
    
    % Find shortest path given all paths using accumulating parameters:
    find_shortest([],ShortestPath,_,ShortestPath).
    
    find_shortest([Path1|Paths],_CurrentShortestPath,CurrentLength,ShortestPath):-
            length(Path1,Length1), Length1 < CurrentLength, !,
            find_shortest(Paths,Path1,Length1,ShortestPath).
    
    find_shortest([_|Paths],CurrentShortestPath,CurrentLength,ShortestPath):-
            find_shortest(Paths,CurrentShortestPath,CurrentLength,ShortestPath).
    

Mixing chemical products

advice(List):-
        findall(Reactval,(reacts(A,B,Reactval),member(A,List),member(B,List)),ReactList),
	list_sum(ReactList,Sum,0),
	message(Sum,Text),
	write(Text),nl.
	
	
list_sum([],Result,Result).
list_sum([H|T],Result,Acc):-
        NAcc is H+Acc,        
	list_sum(T,Result,NAcc).
The message/2 predicate is the same as that of session 3.

The classification problem

Extra list exercises

  1. squareboard(B,Width):-
    	length(B,Width),
    	rows(B,Width).
    rows([],_).
    rows([A|Tail],Width):-
    	length(A,Width),
    	rows(Tail,Width).
    
  2. validboard(B):-
    	length(B,8), % the number of rows should be 8
    	validrows(B).
    validrows([]).
    validrows([R|Tail]):-
    	length(R,8), % each row should have 8 elements
    	allmember(R,[b,w,o]), % each element should be b, w or o
    	validrows(Tail).
    allmember([],_).
    allmember([A|Tail],List):-
    	member(A,List),
    	allmember(Tail,List).
    
    Note that member/2 is not a built-in predicate. In SWI, however, it is automatically loaded at start-up. If you use another prolog engine, you might have to define member/2 yourself.