How do I replace all appearances of X from a list with X+1 ? I’m very new to this.
Like this:
repl([], []).
repl([X|Xs], [Y|Ys]) :-
Y is X+1,
repl(Xs, Ys).
% Run a Goal and print it.
test(Goal) :-
Goal,
writeq(Goal), nl.
% Version 1
plus_list(L0, L) :- maplist(plus1, L0, L).
plus1(X, Y) :- Y is X + 1.
?- test( plus_list([1,2,3], _Result) ).
% Version 2 (generalized to add "N" to each element)
plus_list(N, L0, L) :- maplist(plus(N), L0, L).
plus(N, X, Y) :- Y is X + N.
?- test( plus_list(2, [1,2,3], _Result) ).
% Version 3 (using "lambda")
:- use_module(library(yall)).
plus_list_(N, L0, L) :- maplist({N}/[X,Y]>>(Y is X + N), L0, L).
?- test( plus_list_(3, [1,2,3], _Result) ).
That’s overkill…
Maybe; but it avoids a certain amount of boilerplate, and makes the code easier to understand.
Functional programmers learn the equivalent of maplist/3, foldl/5, etc. early, and they’re equally useful for logic programming. (And if you’re worried about efficiency, you can use library(apply_macros) instead of library(apply).)
Yes, I know. But I find it cumbersome in Prolog. In Haskell, this would be all that is needed, to define a funktion “repl” which adds one to the elements of a list:
repl = map (+1)
which is equivalent to (with different parameter ordering):
repl n l = map (\x -> x + n) l
is a bit more readable, especially if you want a different parameter ordering (and not all functional languages have currying). Logic programming languages aren’t as compact with functions (because they have to use predicate notation) and it’s a design choice as to whether or not be explicit about the “outer” values:
repl(N,L0,L) :- maplist({N}/[X,Y]>>(Y is X+N),L0,L).
That “repl n l = …” of yours, coulde be written this way:
repl n = map (+n)
As far as I’m concerned, I find this shorter notation easier to read.
However, I don’t know this yet:
repl(N,L0,L) :- maplist({N}/[X,Y]>>(Y is X+N),L0,L).
Looks like it is more concise and readable, but I still find it messy. I’ts nothing compared to the elegant Haskell syntax.
Bye
When I read a Haskell definition like this, I mentally add arguments so that it’s equivalent to
repl n l = map (\x -> x+n) l
and in general, I find point-free notation difficult to understand; so for me, the explicit "lambda"s provided by library(yall) are easier to understand, even if more verbose. I wonder if I would change my mind if I did more Haskell programming …
My guess is that most people have my difficult in understanding point-free style because Haskell provides list comprehensions (which only saves a few keystrokes in this case, but is nicer when destructuring is involved):
repl n l = [x+n | x <- l]
Prolog only provides the maplist/3 form (or setof/3 et al, if using a generator). I think I saw a discussion about list comprehensions in Prolog, but can’t remember where …
Hi!
When reading that " repl n = map (+n)
", I don’t mentally add the “missing” arguments. It’s another way of perceiving the same thing. I actually find it easier to understand in the compact way.
Well possible that you would change your mind, if you did more Haskell programming.
Neat! I wasn’t aware of that plus/3 thing. Thanks!
Cheers,
Volker
I wonder if there’s an equivalent of “point-free” notation for logic programming … composition of predicates seems to require variables - or does it? (And this also leads to the clunkiness of evaluating functions in Prolog, such as
count([], 0).
count([_|Xs], Count) :- count(Xs, Count0), Count is Count + 1.
compared to
count [] = 0
count (_:xs) = 1 + count xs
And, yes, in both Prolog and Haskell it’s better to use accumulators or foldl
:
count_list(List, Count) :- foldl([_,C0,C]>>(C is C0+1), List, 0, Count).
count_list = foldl (\ _ c0 -> c0+1) 0
Maybe something based on the notation in Yedalog could solve this …