
Hi, a friend of mine wanted to write function (in Perl) that creates all tuples of length 3 of the elements of a given list, e.g. [(0,0,0),(0,0,1),(0,0,2),...,(5,5,5)] for the list [0..5]. Trying to get better at Haskell, I wrote a small function using the list monad for this (tuples replaced with lists) all3 ls = do a <- ls b <- ls c <- ls return [a,b,c] Now I want to make it capable to create all combinations of length n instead of fixed length 3 (that's why list instead of tuple), but I don't really see how. As the do notation translates to ls >>= \a -> etc. I thought it should be possible to have some sort of "foldr (>>=)" over a list of length n, but I can't figure out how to collect the variable number of results in a list for the "return". Any hints for that? best regards Matthias -- __________________________________________________________ ___ __ __ Dipl. Inf. Matthias Guedemann / __\/ _\ /__\ Computer Systems in Engineering / / \ \ /_\ Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__ Tel.: 0391 / 67-19359 \____/ \__/\__/ __________________________________________________________

On Fri, Oct 30, 2009 at 12:44 PM, Matthias Guedemann
a friend of mine wanted to write function (in Perl) that creates all tuples of length 3 of the elements of a given list, e.g. [(0,0,0),(0,0,1),(0,0,2),...,(5,5,5)] for the list [0..5]. Trying to get better at Haskell, I wrote a small function using the list monad for this (tuples replaced with lists)
all3 ls = do a <- ls b <- ls c <- ls return [a,b,c]
Almost there : all3 ls = do a <- ls b <- ls c <- ls return (a,b,c) For each element a of list ls , for each element b of the same list ls, and for each element c of the same list ls, make a tuple of them. return the list of tall the tuples. You could also write it with a list comprehension : all3 ls = [ (a,b,c) | a <- ls, b <- ls, c <- ls ] David.

Thanks David,
all3 ls = do a <- ls b <- ls c <- ls return (a,b,c)
For each element a of list ls , for each element b of the same list ls, and for each element c of the same list ls, make a tuple of them. return the list of tall the tuples.
But it is a bit more complicated. I changed the result to [a,b,c] in order to have variable length results. I am now trying to get a "allN ls n" function that returns the result for the original problem with "allN [0..5] 3" and all combinations of the form [a,b] with "allN [0..5] 2". So basically I want a variable number of name bindings in the list comprehension. Is this possible in a (simple) way using the list monad? Maybe like allN ls n = foldr (>>=) [] (replicate n ls) >>= return regards, Matthias -- __________________________________________________________ ___ __ __ Dipl. Inf. Matthias Guedemann / __\/ _\ /__\ Computer Systems in Engineering / / \ \ /_\ Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__ Tel.: 0391 / 67-19359 \____/ \__/\__/ __________________________________________________________

Hi Matthias, On Fri, Oct 30, 2009 at 12:44:41PM +0100, Matthias Guedemann wrote:
Hi,
a friend of mine wanted to write function (in Perl) that creates all tuples of length 3 of the elements of a given list...
all3 ls = do a <- ls b <- ls c <- ls return [a,b,c]
Now I want to make it capable to create all combinations of length n instead of fixed length 3 (that's why list instead of tuple), but I don't really see how.
How about a recursive function like this: alln 1 ls = map (:[]) ls alln n ls = do a <- ls as <- alln (n-1) ls return (a:as) Note that `ls :: [t]` and `all (n-1) ls :: [[t]]` has different types but it's okay because both are in the list monad. Also, it can be done with list comprehensions: alln' 1 ls = [[a] | a<-ls] alln' n ls = [a:as | a<-ls, as<-alln' (n-1) ls] Sincerely, jan. -- Heriot-Watt University is a Scottish charity registered under charity number SC000278.

How about a recursive function like this:
alln 1 ls = map (:[]) ls alln n ls = do a <- ls as <- alln (n-1) ls return (a:as)
Note that `ls :: [t]` and `all (n-1) ls :: [[t]]` has different types but it's okay because both are in the list monad.
Also, it can be done with list comprehensions:
alln' 1 ls = [[a] | a<-ls] alln' n ls = [a:as | a<-ls, as<-alln' (n-1) ls]
Works great, thanks a lot Matthias -- __________________________________________________________ ___ __ __ Dipl. Inf. Matthias Guedemann / __\/ _\ /__\ Computer Systems in Engineering / / \ \ /_\ Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__ Tel.: 0391 / 67-19359 \____/ \__/\__/ __________________________________________________________

On Fri, Oct 30, 2009 at 12:44 PM, Matthias Guedemann
Now I want to make it capable to create all combinations of length n instead of fixed length 3 (that's why list instead of tuple), but I don't really see how.
If I understood what you ask this time, there's a function in Control.Monad that does it : allN = replicateM replicateM 4 [ 1,2,3 ] = [ [ 1,1,1,1],[1,1,1,2], .... when you write a <- ls b <- ls c <- ls You perform the monad "action" 3 times, collecting the result in a then b, then c. now replicateM performs a monad action n times, collecting the result in a list. turns out that making a list of the result is exactly what you want. David.

Hallo David,
If I understood what you ask this time, there's a function in Control.Monad that does it : allN = replicateM
replicateM 4 [ 1,2,3 ] = [ [ 1,1,1,1],[1,1,1,2], ....
that is exactly what I wanted, thanks a lot. Next time I will state the question more clearly :-)
when you write
a <- ls b <- ls c <- ls
You perform the monad "action" 3 times, collecting the result in a then b, then c. now replicateM performs a monad action n times, collecting the result in a list. turns out that making a list of the result is exactly what you want.
Maybe I should have a closer look at Control.Monad, a lot seems to be there already. best regards, Matthias -- __________________________________________________________ ___ __ __ Dipl. Inf. Matthias Guedemann / __\/ _\ /__\ Computer Systems in Engineering / / \ \ /_\ Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__ Tel.: 0391 / 67-19359 \____/ \__/\__/ __________________________________________________________

Am Freitag 30 Oktober 2009 12:44:41 schrieb Matthias Guedemann:
Hi,
a friend of mine wanted to write function (in Perl) that creates all tuples of length 3 of the elements of a given list, e.g. [(0,0,0),(0,0,1),(0,0,2),...,(5,5,5)] for the list [0..5]. Trying to get better at Haskell, I wrote a small function using the list monad for this (tuples replaced with lists)
all3 ls = do a <- ls b <- ls c <- ls return [a,b,c]
Now I want to make it capable to create all combinations of length n instead of fixed length 3 (that's why list instead of tuple), but I don't really see how. As the do notation translates to
ls >>= \a -> etc.
I thought it should be possible to have some sort of "foldr (>>=)" over a list of length n, but I can't figure out how to collect the variable number of results in a list for the "return".
Recursive version first: combinations 0 _ = [[]] -- whatever the list, there's one way to pick 0 elements combinations n xs = do h <- xs t <- combinations (n-1) xs return (h:t) (check for n < 0 omitted) So, what are we doing? We have one list of a (xs) and one list of [a] (ys = combinations (n-1) xs) and cons each element of xs to each element of ys: f xs ys = [h:t | h <- xs, t <- ys] = concat [[h:t | t <- ys] | h <- xs] = concat [map (h:) ys | h <- xs] = concat (map (\h -> map (h:) ys) xs) = xs >>= \h -> map (h:) ys That gives combinations n xs = foldr f [[]] (replicate n xs) pointfree, for extra goodness: -- pointfree f inline combinations n xs = foldr ((. (. (:)) . flip map) . (>>=)) [[]] (replicate n xs) -- eliminate xs combinations n = foldr ((. (. (:)) . flip map) . (>>=)) [[]] . replicate n -- completely pointfree combinations = (foldr ((. (. (:)) . flip map) . (>>=)) [[]] .) . replicate
Any hints for that?
best regards Matthias

Hi Daniel,
That gives
combinations n xs = foldr f [[]] (replicate n xs)
pointfree, for extra goodness:
-- pointfree f inline combinations n xs = foldr ((. (. (:)) . flip map) . (>>=)) [[]] (replicate n xs) -- eliminate xs combinations n = foldr ((. (. (:)) . flip map) . (>>=)) [[]] . replicate n -- completely pointfree combinations = (foldr ((. (. (:)) . flip map) . (>>=)) [[]] .) . replicate
thank you, looks rather strange to me but works well. regards -- __________________________________________________________ ___ __ __ Dipl. Inf. Matthias Guedemann / __\/ _\ /__\ Computer Systems in Engineering / / \ \ /_\ Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__ Tel.: 0391 / 67-19359 \____/ \__/\__/ __________________________________________________________

Am Freitag 30 Oktober 2009 14:32:35 schrieb Matthias Guedemann:
Hi Daniel,
That gives
combinations n xs = foldr f [[]] (replicate n xs)
pointfree, for extra goodness:
-- pointfree f inline combinations n xs = foldr ((. (. (:)) . flip map) . (>>=)) [[]] (replicate n xs) -- eliminate xs combinations n = foldr ((. (. (:)) . flip map) . (>>=)) [[]] . replicate n -- completely pointfree combinations = (foldr ((. (. (:)) . flip map) . (>>=)) [[]] .) . replicate
thank you, looks rather strange to me but works well.
Yes :D The pointfree f is nicely obfuscated. But if your friend is a perl coder, he should be able to appreciate that. The standard way to express f, however, is liftM2 (:), so combinations = (foldr (liftM2 (:)) [[]] .) . replicate -- isn't that boring? But earnestly, replicateM is the thing to use.
regards

Yes :D The pointfree f is nicely obfuscated. But if your friend is a perl coder, he should be able to appreciate that.
Honestly, he just wanted a "one-loop-using solution" and was not too interested in anything using Haskell :-)
The standard way to express f, however, is liftM2 (:), so
combinations = (foldr (liftM2 (:)) [[]] .) . replicate -- isn't that boring?
true, it's almost readable At the moment trying to use pointfree is basically pointless for me, more practice is needed. regards Matthias -- __________________________________________________________ ___ __ __ Dipl. Inf. Matthias Guedemann / __\/ _\ /__\ Computer Systems in Engineering / / \ \ /_\ Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__ Tel.: 0391 / 67-19359 \____/ \__/\__/ __________________________________________________________

"Matthias" == Matthias Guedemann
writes:
Matthias> true, it's almost readable At the moment trying to use Matthias> pointfree is basically pointless for me, more practice Matthias> is needed. Actually the pointless style does have a point - like all jargon, it shows that you're a member of the club, and can look down on those who don't understand it. In support of this, it deliberately confuses beginners by omitting the arguments that should be there according to the signature (this is a principle purpose of currying, to confuse beginners :-) ). I cheat - I use hlint, and write the pointless versions that it tells me I should write instead of the pointed version that I write. Is there a "Bluffer's guide to Haskell"? -- Colin Adams Preston Lancashire

2009/10/30 Colin Paul Adams
Is there a "Bluffer's guide to Haskell"?
Whilst not a bluffers guide, this one contains several dozen flavours of 'obscurantism' (** add your less pejorative term here **) http://www.willamette.edu/~fruehr/haskell/evolution.html Methinks your being a bit hard on the pointfree style, but it does often diminish an _operation reading_ of the code (you can tell what the code does from looking at it). So you either have to trust it, or work it out to some expanded form you are happy with. For what its worth I came up with this bit of golf which saves a few keystrokes if you're prepare not to count the helper functions (I consider them generally useful): combinations :: Int -> [a] -> [[a]] combinations = foldr (<:>) [[]] `oo` replicate -- Helpers that I like but are not in the libraries -- | Applicative 'cons'. Equivalent to - liftA2 (:) - but I like having it around. -- The monadic version is attributable to a parser library in Clean. (<:>) :: Applicative f => f a -> f [a] -> f [a] (<:>) a b = (:) <$> a <*> b -- | Compose an arity 1 function and an arity 2 function. -- -- I call this combinator 'specs' (aka glasses) due to its infix -- appearance `oo` - I believe fans of Raymond Smullyan's -- 'To Mock a Mockingbird' call it blackbird... oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d oo f g = (f .) . g Best wishes Stephen

Am Freitag 30 Oktober 2009 17:27:12 schrieb Stephen Tetley:
2009/10/30 Colin Paul Adams
: Is there a "Bluffer's guide to Haskell"?
Whilst not a bluffers guide, this one contains several dozen flavours of 'obscurantism' (** add your less pejorative term here **)
http://www.willamette.edu/~fruehr/haskell/evolution.html
Methinks your being a bit hard on the pointfree style, but it does often diminish an _operation reading_ of the code (you can tell what the code does from looking at it). So you either have to trust it, or work it out to some expanded form you are happy with.
Completely pointfree style tends to be unreadable except for the selected few. It's fun to create pointfree versions of your functions, and you learn something by doing that, but it should appear rarely in your code. Completely pointful style tends to be not unreadable, but often cluttered. The most readable is usually a "partially pointfree" style. Which degree of pointfreeness is most readable depends of course on the reader, but there's a range which most can agree is good. Function combinators and pipelines should be partially pointfree: foo = bar . baz . hum is better than foo x = bar (baz (hum x)) or foo x = bar $ baz $ hum x or foo x = bar . baz . hum $ x flurb f g = f . g . f is better than flurb f g = f (g (f x)) wibble f g = f &&& g >>> g *** f is better than wibble f g x = f &&& g >>> g *** f $ x - but worse than wibble f g = (f &&& g) >>> (g *** f) because the latter doesn't require knowledge of the fixities to parse. However, wibble f g = (g . f) &&& (f . g) is at least as good if you want it only for the Category (->). Whether that is better than wibble f g x = (g (f x), f (g x)) depends on how familiar one is with Control.Arrow. Writing flurb or wibble completely pointfree is a nightmare :) Which is best: a) incrementAll n xs = map (\x -> x+n) xs b) incrementAll n xs = map (+n) xs c) incrementAll n = map (+n) d) incrementAll = map . (+) ? None of them is unreadable - though d) is confusing in the first few weeks of Haskell - but b) and c) are clearly better than the other two and c) is a bit better than b) in my opinion. Would you prefer: a) comb = flip (.) (flip (.)) (flip (.) (flip (.))) b) comb = (. flip (.)) . flip (.) c) comb f = (. f) . flip (.) d) comb f g = (. g) . f e) comb f g x = f x . g f) comb f g x y = f x (g y) ? a) is the prettiest, but honestly, I'd rather not meet it in code. e) is best, f) is okay, d) acceptable.
For what its worth I came up with this bit of golf which saves a few keystrokes if you're prepare not to count the helper functions
That's cheating (until they are in a library).
(I consider them generally useful):
Yup.
combinations :: Int -> [a] -> [[a]] combinations = foldr (<:>) [[]] `oo` replicate
-- Helpers that I like but are not in the libraries
-- | Applicative 'cons'. Equivalent to - liftA2 (:) - but I like having it around. -- The monadic version is attributable to a parser library in Clean.
(<:>) :: Applicative f => f a -> f [a] -> f [a] (<:>) a b = (:) <$> a <*> b
I'd prefer either (<:>) = liftA2 (:) or a <:> b = (:) <$> a <*> b
-- | Compose an arity 1 function and an arity 2 function. -- -- I call this combinator 'specs' (aka glasses) due to its infix -- appearance `oo` - I believe fans of Raymond Smullyan's -- 'To Mock a Mockingbird' call it blackbird...
oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d oo f g = (f .) . g
This is sometimes also denoted by (.:), it has the pretty definition (.:) = (.) . (.)
Best wishes
Stephen

Hello Matthias,
you may want to have a look at section 11 of my monads tutorial [1],
which contains monadic library functions like replicateM together with
examples and detailed explanations.
[1] http://ertes.de/articles/monads.html#section-11
Greets,
Ertugrul.
Matthias Guedemann
Hi,
a friend of mine wanted to write function (in Perl) that creates all tuples of length 3 of the elements of a given list, e.g. [(0,0,0),(0,0,1),(0,0,2),...,(5,5,5)] for the list [0..5]. Trying to get better at Haskell, I wrote a small function using the list monad for this (tuples replaced with lists)
all3 ls = do a <- ls b <- ls c <- ls return [a,b,c]
Now I want to make it capable to create all combinations of length n instead of fixed length 3 (that's why list instead of tuple), but I don't really see how. As the do notation translates to
ls >>= \a -> etc.
I thought it should be possible to have some sort of "foldr (>>=)" over a list of length n, but I can't figure out how to collect the variable number of results in a list for the "return".
Any hints for that?
best regards Matthias
-- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

Hello Ertugrul, this looks interesting. I read Brent Yorgeys Typeclassopedia and also the work you cite in your tutorial. So I am trying to learn about Applicative, Monoids, Monads etc. by using them. Your description of the library functions comes handy, as reading the source directly does not really help if you're still struggling with understanding the concepts. And on the other hand, due to the abstract nature of monads, a lot of functionality should be "hidden" in the library (just like my rewrite of replicateM) thank you very much, will read it on the weekend regards Matthias Excerpts from Ertugrul Soeylemez's message of Fr Okt 30 15:01:29 +0100 2009:
Hello Matthias,
you may want to have a look at section 11 of my monads tutorial [1], which contains monadic library functions like replicateM together with examples and detailed explanations.
[1] http://ertes.de/articles/monads.html#section-11
Greets, Ertugrul.
Matthias Guedemann
wrote: Hi,
a friend of mine wanted to write function (in Perl) that creates all tuples of length 3 of the elements of a given list, e.g. [(0,0,0),(0,0,1),(0,0,2),...,(5,5,5)] for the list [0..5]. Trying to get better at Haskell, I wrote a small function using the list monad for this (tuples replaced with lists)
all3 ls = do a <- ls b <- ls c <- ls return [a,b,c]
Now I want to make it capable to create all combinations of length n instead of fixed length 3 (that's why list instead of tuple), but I don't really see how. As the do notation translates to
ls >>= \a -> etc.
I thought it should be possible to have some sort of "foldr (>>=)" over a list of length n, but I can't figure out how to collect the variable number of results in a list for the "return".
Any hints for that?
best regards Matthias
-- __________________________________________________________ ___ __ __ Dipl. Inf. Matthias Guedemann / __\/ _\ /__\ Computer Systems in Engineering / / \ \ /_\ Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__ Tel.: 0391 / 67-19359 \____/ \__/\__/ __________________________________________________________
participants (7)
-
Colin Paul Adams
-
Daniel Fischer
-
David Virebayre
-
Ertugrul Soeylemez
-
Jan Jakubuv
-
Matthias Guedemann
-
Stephen Tetley