Inserting value into the begining of each sublist - list

I'm currently writing a predicate that will run through a list of lists and insert a value I have calculated onto the beginning of the list
Step one is easy, just perform the calculation for each list and unify variable N with it.
checkthrough([]).
checkthrough([H|T]):-
count_validentries(H,N),
checkthrough(T).
What I'm trying to achieve now is to put that variable N onto the beginning of each of my sublists, so each list begins with the count of valid entries.
I have attempted to do this using an accumulator. Attempting to start with an empty list, and to every time add the new value N and the head of the list to it:
checkthrough([],Sofar,Lastone).
checkthrough([H|T],Sofar,Lastone):-
count_validentries(H,N),
Newsofar is [N,H|Sofar],
checkthrough(T,Newsofar,Lastone).
I'm quite sure I'm making a really stupid mistake somewhere along the lines. This is not valid Prolog syntax, failing with Arithmetic:' [2 internal variables]' is not a function.
Does anyone have any tips please?

Using meta-predicate maplist/3 and Prolog lambda simply write:
?- use_module(library(lambda)).
?- maplist(\Es^[N|Es]^count_validentries(Es,N), Ess, Xss).
Also, I'd guess that you're really looking for (-)/2 pairs which is how key-value pairs are commonly represented—by library predicates and the built-in predicate keysort/2. Consider:
?- Ess = [[a,b,c],[d,e],[],[f]],
maplist(\Es^(N-Es)^length(Es,N), Ess, Xss),
keysort(Xss, Yss).
Ess = [ [a,b,c], [d,e], [], [f]],
Xss = [3-[a,b,c], 2-[d,e], 0-[], 1-[f]],
Yss = [0-[], 1-[f], 2-[d,e], 3-[a,b,c]].

Maybe
checkthrough([],Sofar,Sofar).
checkthrough([H|T],Sofar,Lastone):-
count_validentries(H,N),
checkthrough(T,[[N|H]|Sofar],Lastone).
but you'll end up with the list reversed. Keeping it simpler will help
checkthrough([],[]).
checkthrough([H|T],[[N|H]|Rest]):-
count_validentries(H,N),
checkthrough(T,Rest).
or better, if you're running a recent version of SWI-Prolog:
checkthrough(L,L1) :-
maplist([E,E1]>>(count_validentries(E,N),E1=[N|E]), L,L1).

Related

Reverse every second list of lists in Prolog

I have a list containing lists and I want to reverse every second list in it. I tried something but if I have odd number of elements in the list the last list element is lost... So the best solution would be to put the odd lists first and the even lists second till every second list is reversed.
I can't use any libraries. I need to do it recursively or split them and append them again. The best thing I made so far was to reverse only the first even list and append the first odd and even list in a new list.
I tried to do this:
reverselist(List, [List]).
reverselist([X,Y|Rest], [SnakeList|Rest2]):-
append(X, [], Odd),
reverse(Y, EvenList),
append(Odd, EvenList, SnakeList),
reverselist(Rest, Rest2).
And this:
reverselist(List1, List2).
reverselist([H|Ts], [Odd|R]):-
not(0 is H mod 2),
append(H, [], Odd),
reverselist(Ts, R).
reverselist([H|Ts], [Even|R]):-
0 is H mod 2,
reverse(H, Even),
reverselist(Ts, R).
Sample query:
?- reverselist([[a,b,c],[d,a,b],[c,d,o],[b,c,d],[e,e,d]], List).
I want the result to be:
List = [ [a,b,c],[b,a,d],[c,d,o],[d,c,b],[e,e,d] ].
You can also write mutual recursion:
reverselist([],[]).
reverselist([H|T],[H|T1]):-reverselist2(T,T1).
reverselist2([],[]).
reverselist2([H|T],[H1|T1]):-reverse(H,H1), reverselist(T,T1).
You were pretty close with your first variant.
Instead of your
reverselist(List, [List]).
reverselist([X,Y|Rest], [SnakeList|Rest2]):-
append(X, [], Odd),
reverse(Y, EvenList),
append(Odd, EvenList, SnakeList),
reverselist(Rest, Rest2).
just tweak it as
reverselist([], []). % additional clause
reverselist([List], [List]).
reverselist([X,Y|Rest], [X,EvenList|Rest2]):-
reverse( Y, EvenList),
reverselist( Rest, Rest2).
All three clauses are mutually exclusive and together they are exhaustive, i.e. they cover every possibility.
I believe this definition to be the most immediate and close representation of your problem. In Prolog, to formulate the problem means to have the solution for it.
We need to create another predicate with one more argument to keep track of odd or even position:
reverselist(InList,OutList):- reverselist(InList,OutList, 0).
reverselist([],[],_). %base case
%case of even position
reverselist([H|T],[H|T1], 0):- reverselist(T,T1,1).
%case of odd position
reverselist([H|T],[H1|T1], 1):- reverse(H1,H), reverselist(T,T1,0).

Write a predicate sqrt_list(NumberList, ResultList) to the list of pairs consisting of a number and its square root

Write a predicate sqrt_list(NumberList, ResultList) that binds ResultList to the list of pairs consisting of a number and its square root, for each number in NumberList.
For example:
?- sqrt_list([1,4,9], Result).
Result = [[1,1.0], [4,2.0], [9,3.0]]. % expected
Using the meta-predicate maplist/3 in combination with library(lambda):
:- use_module(library(lambda)).
list_withsqrts(Es, Xss) :-
maplist(\E^[E,S]^(S is sqrt(E)), Es, Xss).
Sample query:
?- list_withsqrts([1,4,9], Xss).
Xss = [[1,1.0], [4,2.0], [9,3.0]].
A few notes:
Using fixed-length lists instead of compound terms of the same arity is generally regarded as bad coding style.
Finding good relation names is an important Prolog programming skill. In above code I used list_withsqrts instead of sqrt_list. Not famous, but arguably somewhat better...
keep dividing the original list into sublist, taking one number as head and rest as a tail. repeat the same and Note that the Prolog built-in function sqrt computes the square root and that it needs to be evaluated using is to actually do the computation:
example:
?- X is sqrt(5).
X = 2.23606797749979.
then add each result to the resultList head with numberList. as,
ResultHead=[Head|[SquareRoot]]

How to write a prolog predicate to trim first N elements from a List using conc (concatenation) operation

trim(L1,N,L2) which is true if L2 contains the first N elements of L1
I'm required to write the prolog code using the relation conc. Im new to prolog, so i have issue with my code. Can somebody correct me?
trim(L1, N, L2):- conc(L2,T,L1), length(L2,N),length(L1,N2), N2>= N
Most people have written the code using append and recurssion too. Please be kind enough to help me to use conc.
trim(L1,N,L2):-conc(L3,_,L1),conc(L2,_,L3),length(L2,N),!.
You are nearly there. Just make 'T' anonymous and you are good to go.
conc([],L,L).
conc([Head|L1],L2,[Head|L]):-conc(L1,L2,L).
trim(L1,N,L2) :-conc(L2,_,L1) ,length(L2,N).
And ask queries.
?- trim([1,2,3],1,X).
X = [1] ;
?- trim([1,2,3],0,X).
X = [] ;
?- trim([1,2,3],2,[1,2]).
true.

Get longest list as goal in prolog

I have more possible list as goal,but i need only one longest list.Is this possible to get first longest list?
li-->[a]|[b]|[c].
int-->['1']|['2']|['3'].
num-->int,num_nl.
num_nl-->num|[].
list1-->num,li.
classify(L,S,R):-list1(S,[]),extract(S,L,R).
extract(S,L1,L2):-append(L11,L22,L1),append(S,L3,L22),append(L11,L3,L2).
Here ERROR: Out of local stack.I want only longest list as goal:
?-classify([c,'1','1',a,f],S,R).
S = ['1', '1', a], R = [c, f] ;
false.
?-classify([c,'1','2','3',a,f,'1','1','2','3',b],S,R).
S = ['1','2','3',a], R = [c, f,'1','1','2','3',b] ;
false.`
You don't provide any detail on how classify/1 is implemented; it could be that you can define it so that it only gives you the longest list.
Your other option is to collect all results, using either findall/3 or bagof/3 or setof/3, then make pairs with the list length as the first element, then sort these pairs and pick the last.
For example:
?- bagof(X, classify(X), Xs),
maplist(length, X, Lengths),
pairs_keys_values(Ps, Lengths, Xs),
keysort(Ps, Sorted),
last(_-Longest, Sorted).
It uses pairs_keys_values/3 and last/2 as defined in the SWI-Prolog standard libraries.
This approach will work, even though it has several problems. It is difficult to discuss those without any knowledge of what classify/1 does.
I used at least once a convoluted variant of Boris' answer
?- R=[_-S|_],setof(L-X,T^(classify(X),length(X,T),L is -1*T),R).

Removing heads from lists in Prolog

I'm trying to write a predicate to remove the head from every list in list of lists and add the tails to a new list. The resulting list should be returned as the second parameter.
Here's the attempt:
construct_new(S,New) :-
New = [],
new_situation(S,New).
new_situation([],_).
new_situation([H|T], New) :-
chop(H, H1),
new_situation(T, [H1|New]).
chop([_|T], T).
You would call it like this:
construct_new([[x,x],[b,c],[d,e,f]],S).
This, however, only produces output true..
Step-by-step execution
Your query is construct_new(Input,Output), for some instanciated Input list.
The first statement in construct_new/2 unifies Output (a.k.a. New) with the empty list. Where is the returned list supposed to be available for the caller? Both arguments are now unified.
You call new_situation(Input,[])
You match the second clause new_situation([H|T],[]), which performs its task recursively (step 4, ...), until ...
You reach new_situation([],_), which successfully discards the intermediate list you built.
Solutions
Write a simple recursive predicate:
new_situation([],[]).
new_situation([[_|L]|T],[L|R]) :-
new_situation(T,R).
Use maplist:
construct_new(S,R) :-
maplist(chop,S,R).
Remark
As pointed out by other answers and comments, your predicates are badly named. construct_new is not a relation, but an action, and could be used to represent almost anything. I tend to like chop because it clearly conveys the act of beheading, but this is not an appropriate name for a relation. repeat's list_head_tail(L,H,T) is declarative and associates variables to their roles. When using maplist, the other predicate (new_situation) doesn't even need to exist...
...even though guillotine/3 is tempting.
This could be done with a DCG:
owth(Lists, Tails) :-
phrase(tails(Tails), Lists).
tails([]) --> [].
tails([T|Tails]) --> [[_|T]], tails(Tails).
Yielding these queries:
| ?- owth([[x,x],[b,c],[d,e,f]], T).
T = [[x],[c],[e,f]] ? ;
no
| ?- owth(L, [[x],[c],[e,f]]).
L = [[_,x],[_,c],[_,e,f]]
yes
(owth = Off with their heads! or, if used the other direction, On with their heads!)
If you also want to capture the heads, you can enhance it as follows:
owth(Lists, Heads, Tails) :-
phrase(tails(Heads, Tails), Lists).
tails([], []) --> [].
tails([H|Hs], [T|Tails]) --> [[H|T]], tails(Hs, Tails).
We use meta-predicate maplist/[3-4] with one of these following auxiliary predicates:
list_tail([_|Xs],Xs).
list_head_tail([X|Xs],X,Xs).
Let's run some queries!
?- maplist(list_head_tail,[[x,x],[b,c],[d,e,f]],Heads,Tails).
Heads = [x,b,d],
Tails = [[x],[c],[e,f]].
If you are only interested in the tails, use maplist/4 together with list_head_tail/3 ...
?- maplist(list_head_tail,[[x,x],[b,c],[d,e,f]],_,Tails).
Tails = [[x],[c],[e,f]].
... or, even simpler, maplist/3 in tandem with list_tail/2:
?- maplist(list_tail,[[x,x],[b,c],[d,e,f]],Tails).
Tails = [[x],[c],[e,f]].
You can also use the somewhat ugly one-liner with findall/3:
?- L = [[x,x],[b,c],[d,e,f]],
findall(T, ( member(M, L), append([_], T, M) ), R).
R = [[x], [c], [e, f]].
(OK, technically a two-liner. Either way, you don't even need to define a helper predicate.)
But definitely prefer the maplist solution that uses chop as shown above.
If you do the maplist expansion by hand, and name your chop/2 a bit better, you would get:
lists_tails([], []).
lists_tails([X|Xs], [T|Ts]) :-
list_tail(X, T),
lists_tails(Xs, Ts).
And since you can do unification in the head of the predicate, you can transform this to:
lists_tails([], []).
lists_tails([[_|T]|Xs], [T|Ts]) :-
lists_tails(Xs, Ts).
But this is identical to what you have in the other answer.
Exercise: why can't we say:
?- maplist(append([_]), R, [[x,x],[b,c],[d,e,f]]).