Solutions for Session 3

  1. Not every pair that somewhere contains a list is a list itself. For example .([],1) is a pair which is not a list although it contains the empty list (it is not a list because the second element of the pair is not a list).

  2. The first and third query will fail. The second query will succeed and results in the following bindings:
    A = a
    B = [b,c]
    C = d
    
  3. ?- .(a, .(b, .(c,.(d,[])))) = [A,B|C].
    A = a
    B = b
    C = [c,d]
    Yes 
    
    ?- [A|B] = .(a, .(.(b,.(c,[])),.(d,[]))).
    A = a
    B = [[b,c],d]
    Yes 
    
    ?- [A,B|C] = .(a, .(.(b,.(c,[])),.(d,[]))).
    A = a
    B = [b,c]
    C = [d]
    Yes 
    
    ?- [ a, b | [] ] = [ H | T].
    H = a
    T = [b]
    Yes 
    
    ?- [ a, b, c] = [ E1, E2 | T ].
    E1 = a
    E2 = b
    T = [c]
    Yes 
    
    ?- X = a, Y = [ 1, [2,3] ], Z = [X | Y].
    X = a
    Y = [1,[2,3]]
    Z = [a,1,[2,3]]
    Yes 
    
    ?- X = a, Y = [ 1, [2,3] ], Z = [X,Y].
    X = a
    Y = [1,[2,3]]
    Z = [a,[1,[2,3]]]
    Yes 
    
    ?- X = [a], Y = [ 1, [2,3] ], Z = [X | Y].
    X = [a]
    Y = [1,[2,3]]
    Z = [[a],1,[2,3]]
    Yes 
    
  4. ?- listlength([1,[2,3]],L). 
    L = 2
    Yes
    
    ?- listlength([1|[2,3]],L).
    L = 3
    Yes
    
    If you do not see why these are the right answers, draw the tree representations of [1,[2,3]] and [1|[2,3]] (you will see that [1|[2,3]] is the same as [1,2,3]).
  5. listsum([],0).
    listsum([A|Rest],Sum):-
    	listsum(Rest,Sum1),
    	Sum is Sum1 + A.
    
    The most obvious solution for the average is the following:
    listaverage([],0).
    
    listaverage([H|T],Average) :-
    	listsum([H|T],Sum),
    	listlength([H|T],Length),
    	Average is Sum/Length.
    
    In the above solution we traverse the list twice. We can also compute the average by traversing the list only once (which is more efficient):
    listavg(List,Avg):-
    	listsumlength(List,Length,Sum),
    	Avg is Sum / Length.
    
    listsumlength([],0,0).
    listsumlength([A|Rest],Length,Sum):-
    	listsumlength(Rest,Length1,Sum1),
    	Length is Length1 + 1 ,
    	Sum is Sum1 + A.
    
  6. printlist([]):-nl.
    printlist([H|T]):-
            write(H),
    	printlist(T).
    
  7. countdisk([],0).
    countdisk([w|R],C):-countdisk(R,T), C is T + 1 .
    countdisk([b|R],C):-countdisk(R,T), C is T + 1 .
    countdisk([n|R],C):-countdisk(R,C).
    
    The first 4 queries are easy.
    ?- countdisk([w,b,n,n],Count).
    Count = 2
    Yes 
    
    ?- countdisk([w,b,n,n],4).
    No
    
    ?- countdisk([w,b,n,n],2).
    Yes 
    
    ?- countdisk([n,n,n,n,n,n,n,n,n,n],Count).
    Count = 0
    Yes 
    
    The fifth query might seem a bit strange.
    ?- countdisk([w,n,b|Tail],Count).
    
    Tail = []
    Count = 2 ;
    
    Tail = [w]
    Count = 3 ;
    
    Tail = [w, w]
    Count = 4 ;
    
    Tail = [w, w, w]
    Count = 5 ;
    
    We get an infinite number of results. This is because the tail is a variable and for each instantiation of that variable there is an answer.
  8. The nb_rounds/2 predicate:
    nb_rounds([],0).
    nb_rounds([_],1).
    nb_rounds([_,_|Rest],Count):-
    	nb_rounds(Rest,Tempcount),
    	Count is Tempcount + 1 .
    
    ?- nb_rounds(List,Number).
    List = []
    Number = 0
    Yes ;
    List = [_24]
    Number = 1
    Yes ;
    List = [_24,_26]
    Number = 1
    Yes ;
    List = [_24,_26,_29]
    Number = 2
    Yes ;
    List = [_24,_26,_29,_31]
    Number = 2
    Yes ;
    List = [_24,_26,_29,_31,_34]
    Number = 3
    
    and so on

    The split/3 predicate:

    split([],[],[]).
    split([A],[A],[]).
    split([A,B|T],[A|T1],[B|T2]):-
    	split(T,T1,T2).
    
    You do not have to write a merge/3 predicate now that you already have the split/3 predicate! Depending on which arguments you instantiate, you can use split/3 to split a given list into two lists as well as to merge two given lists in another list !!

    To split a given list:

    ?- split([move(b,1,b,3), move(c,10,c,8), move(b,3,b,5)],BlackMoves,WhiteMoves).
    BlackMoves = [move(b,1,b,3),move(b,3,b,5)]
    WhiteMoves = [move(c,10,c,8)]
    Yes 
    
    To merge two given lists:
    ?- split(AllMoves,[move(b,1,b,3), move(b,3,b,5)],[move(c,10,c,8)]).    
    AllMoves = [move(b,1,b,3),move(c,10,c,8),move(b,3,b,5)]
    Yes 
    
  9. reacts(vinegar,salt,25).
    reacts(salt,water,3).
    reacts('brown soap',water,10).
    reacts('pili pili', milk,7).
    reacts(tonic,bailey,8).
    
    reaction(ProdA,ProdB,N) :- 
    	reacts(ProdA,ProdB,N).
    reaction(ProdA,ProdB,N) :- 
    	reacts(ProdB,ProdA,N).
    reaction(ProdA,ProdB,0). % Nothing is known about reaction between ProdA and ProdB
    
    calc_reaction([],0).
    calc_reaction([A|Tail],Nr):-
    	calc_reaction_2(A,Tail,N1),
    	calc_reaction(Tail,N2),
    	Nr is N1+N2.
    
    calc_reaction_2(_,[],0).
    calc_reaction_2(A,[B|Tail],Nr):-
    	reaction(A,B,N1),
    	calc_reaction_2(A,Tail,N2),
    	Nr is N1 + N2.
    
    message(N,'This is a mixture for which no irritation is expected'):-
    	N=<5.
    message(N,'This mixture could cause minor irritation, be careful'):-
    	N=<12, 
    	N>=6.
    message(N,'This mixture causes minor burning wounds, do not use this!'):-
    	N=<20, 
    	N>=13.
    message(N,'Warning: this mixture causes severe burning wounds, never use this!'):-
    	N=<30, 
    	N>=21.
    message(N,'WARNING!! This is a potential lethal mixture!'):- 
    	N>30.
    
    advice(List):-
    	calc_reaction(List,Nr),
    	message(Nr,Message),
    	write(Message),nl.
    
    Here are some queries:
    ?- advice([vinegar,salt,water]).
    Warning: this mixture causes severe burning wounds, never use this!
    Yes
    
    ?- advice([jam, salt, pepper, water, 'red onions', 'brown soap']).
    Warning: this mixture could result in minor burning wounds!
    Yes
    
    ?- advice([vinegar,water,salt,soup,'brown soap']).
    WARNING!! This is a potential lethal mixture!
    Yes 
    
    ?- advice([water]).
    This is a mixture for which no irritation is expected
    Yes 
    
    ?- advice([]).     
    This is a mixture for which no irritation is expected
    Yes 
    
    ?- advice([pineapple,strawberry,tunafish]).          
    This is a mixture for which no irritation is expected
    Yes