howto tuple fold to do n-ary cross product?

http://www.muitovar.com/monad/moncow.xhtml#list contains a cross function which calculates the cross product of two lists. That attached does the same but then used cross on 3 lists. Naturally, I thought use of fold could generalize that to n lists; however, I'm getting error: {-- cut here Compilation started at Sun Nov 23 13:15:24 make runghc -XMultiParamTypeClasses -XFunctionalDependencies -XFlexibleInstances cross.hs cross.hs:23:30: Occurs check: cannot construct the infinite type: a = (a, a) Expected type: [a] -> [a] -> [a] Inferred type: [a] -> [a] -> [(a, a)] In the first argument of `Data.Foldable.foldl1', namely `cross' In the first argument of `print', namely `(Data.Foldable.foldl1 cross (list2, list3, list1))' make: *** [run] Error 1 }-- cut here How do I apply fold to cross and n lists, for n>=0? TIA. -regards, Larry

2008/11/23 Larry Evans
http://www.muitovar.com/monad/moncow.xhtml#list
contains a cross function which calculates the cross product of two lists. That attached does the same but then used cross on 3 lists. Naturally, I thought use of fold could generalize that to n lists; however, I'm getting error:
You should try writing this yourself, it would be a good exercise. To begin with, you can mimic the structure of cross in that tutorial, but make it recursive. After you have a recursive version, you might try switching to fold or foldM. The type of the function will not involve tuples, since they can be arbitrary length (dynamic-length tuples are not supported in Haskell; we use lists for that). cross :: [[a]] -> [[a]] ... Good luck, Luke

On 11/23/08 13:52, Luke Palmer wrote:
2008/11/23 Larry Evans
: http://www.muitovar.com/monad/moncow.xhtml#list
contains a cross function which calculates the cross product of two lists. That attached does the same but then used cross on 3 lists. Naturally, I thought use of fold could generalize that to n lists; however, I'm getting error:
You should try writing this yourself, it would be a good exercise. To begin with, you can mimic the structure of cross in that tutorial, but make it recursive. After you have a recursive version, you might try switching to fold or foldM.
Thanks. The recursive method worked with: -{--cross.hs-- crossr::[[a]] -> [[a]] crossr lls = case lls of { [] -> [] ; [hd] -> map return hd ; hd:tail -> concat (map (\h ->map (\t -> h:t) (crossr tail)) hd) } -}--cross.hs-- However, I'm not sure fold will work because fold (or rather foldr1) from: http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#12 has signature: (a->a->a)->[a]->a and in the cross product case, a is [a1]; so, the signature would be ([a1]->[a1]->[a1]->[[a1]]->[a1] but what's needed as the final result is [[a1]]. Am I missing something? -Larry

It's more natural to consider the cross product of no sets to be [[]] so
your crossr becomes:
crossr [] = [[]]
crossr (x:xs) = concat (map (\h ->map (\t -> h:t) (crossr tail)) hd)
which we can rewrite with list comprehensions for conciseness:
crossr [] = [[]]
crossr (x:xs) = [ a:as | a <- x, as <- crossr xs ]
then look at the definition of foldr:
foldr f z [] = z
foldr f z (x:xs) = f x (foldr f z xs)
and, considering (foldr f z) == crossr, you should derive the definition of
f and z.
On Mon, Nov 24, 2008 at 5:43 AM, Larry Evans
On 11/23/08 13:52, Luke Palmer wrote:
2008/11/23 Larry Evans
: http://www.muitovar.com/monad/moncow.xhtml#list
contains a cross function which calculates the cross product of two lists. That attached does the same but then used cross on 3 lists. Naturally, I thought use of fold could generalize that to n lists; however, I'm getting error:
You should try writing this yourself, it would be a good exercise. To begin with, you can mimic the structure of cross in that tutorial, but make it recursive. After you have a recursive version, you might try switching to fold or foldM.
Thanks. The recursive method worked with: -{--cross.hs-- crossr::[[a]] -> [[a]]
crossr lls = case lls of { [] -> [] ; [hd] -> map return hd ; hd:tail -> concat (map (\h ->map (\t -> h:t) (crossr tail)) hd) } -}--cross.hs--
However, I'm not sure fold will work because fold (or rather foldr1) from: http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#12
has signature:
(a->a->a)->[a]->a
and in the cross product case, a is [a1]; so, the signature would be
([a1]->[a1]->[a1]->[[a1]]->[a1]
but what's needed as the final result is [[a1]].
Am I missing something?
-Larry
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 11/24/08 00:40, Andrea Vezzosi wrote:
It's more natural to consider the cross product of no sets to be [[]] so your crossr becomes:
crossr [] = [[]] crossr (x:xs) = concat (map (\h ->map (\t -> h:t) (crossr tail)) hd)
which we can rewrite with list comprehensions for conciseness:
crossr [] = [[]] crossr (x:xs) = [ a:as | a <- x, as <- crossr xs ]
then look at the definition of foldr: foldr f z [] = z foldr f z (x:xs) = f x (foldr f z xs)
and, considering (foldr f z) == crossr, you should derive the definition of f and z.
THANK YOU Andrea (and Luke) for prompting me to a solution: crossf::[[a]] -> [[a]] crossf lls = foldr (\hd tail -> concat (map (\h ->map (\t -> h:t) tail) hd)) [[]] lls The reason I'm interested in this is that the cross product problem came up in the boost newsgroup: http://thread.gmane.org/gmane.comp.lib.boost.devel/182797/focus=182915 I believe programming the solution in a truly functional language might help a boost mpl programmer to see a solution in mpl. I expect there's some counterpart to haskell's map, concat, and foldr in mpl and so the mpl solution would be similar to the above crossf solution. -kind regards to both of you, Larry

Luke Palmer wrote:
Larry Evans wrote:
contains a cross function which calculates the cross product of two lists. That attached does the same but then used cross on 3 lists. Naturally, I thought use of fold could generalize that to n lists; however, I'm getting error:
The type of the function will not involve tuples, since they can be arbitrary length (dynamic-length tuples are not supported in Haskell; we use lists for that).
cross :: [[a]] -> [[a]]
....
This is the sequence function from Control.Monad. cross :: [[a]] -> [[a]] cross = sequence
cross [[1,2],[3,4]] [[1,3],[1,4],[2,3],[2,4]]
Regards, apfelmus

On 11/23/08 13:52, Luke Palmer wrote:
2008/11/23 Larry Evans
: http://www.muitovar.com/monad/moncow.xhtml#list
contains a cross function which calculates the cross product of two lists. That attached does the same but then used cross on 3 lists. Naturally, I thought use of fold could generalize that to n lists; however, I'm getting error:
You should try writing this yourself, it would be a good exercise. To begin with, you can mimic the structure of cross in that tutorial, but make it recursive. After you have a recursive version, you might try switching to fold or foldM.
The type of the function will not involve tuples, since they can be arbitrary length (dynamic-length tuples are not supported in Haskell; we use lists for that).
cross :: [[a]] -> [[a]]
However, list's contain elements all of the same type. What the
following boost post:
http://thread.gmane.org/gmane.comp.lib.boost.devel/182797/focus=182915
demonstrated was, AFAICT, the c++ template metaprogramming counterpart
to the moncow haskell cross. Now, AFAICT, the boost vault directory:
http://www.boostpro.com/vault/index.php?PHPSESSID=ab51206c9d980155d142f5bcef8e00ee&direction=0&order=&directory=Template%20Metaprogramming
in the cross_nproduct_view_test.zip, contains what I'm looking for
in haskell. I'm guessing that:
template

On Sun, Nov 30, 2008 at 10:25 AM, Larry Evans
Is there some version of haskell, maybe template haskell, that can do that, i.e. instead of:
cross::[[a]] -> [[a]]
have:
crossn::[a0]->[a1]->...->[an] -> [(a0,a1,...,an)]
Ah yes! This is straightforward usage of the list monad. I suggest applicative notation: import Control.Applicative (,,,) <$> xs0 <*> xs1 <*> xs2 <*> xs3 Or alternatively: import Control.Monad liftM4 (,,,) xs0 xs1 xs2 xs3 (I would have used liftA4, but it's not defined. The definition looks a lot like the first example :-) This notation seems a bit magical, but you can build what you want using a simple binary cross: cross :: [a] -> [b] -> [(a,b)] It's just kind of a pain (you build [(a,(b,(c,d)))] and then flatten out the tuples). The applicative notation is a neat little trick which does this work for you. If you're asking whether crossn, as a single function which handles arbitrarily many arguments, can be defined, the short answer is "no". I dare you to come up with a case in which such function adds more than cursory convenience. The long answer is "yes, but you don't want to". It involves mad typeclass hackery, and it doesn't buy you very much. Luke

On Sun, Nov 30, 2008 at 9:30 AM, Luke Palmer
cross :: [a] -> [b] -> [(a,b)]
It's just kind of a pain (you build [(a,(b,(c,d)))] and then flatten out the tuples). The applicative notation is a neat little trick which does this work for you.
It seems to me like this would all be easy if (a,b,c,d) was sugar for (a,(b,(c,d))), and I can't see a disadvantage to that. --Max

On 2008 Nov 30, at 12:43, Max Rabkin wrote:
On Sun, Nov 30, 2008 at 9:30 AM, Luke Palmer
wrote: cross :: [a] -> [b] -> [(a,b)]
It's just kind of a pain (you build [(a,(b,(c,d)))] and then flatten out the tuples). The applicative notation is a neat little trick which does this work for you.
It seems to me like this would all be easy if (a,b,c,d) was sugar for (a,(b,(c,d))), and I can't see a disadvantage to that.
No disadvantage aside from it making tuples indistinguishable from lists. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Sun, 30 Nov 2008, Brandon S. Allbery KF8NH wrote:
On 2008 Nov 30, at 12:43, Max Rabkin wrote:
It seems to me like this would all be easy if (a,b,c,d) was sugar for (a,(b,(c,d))), and I can't see a disadvantage to that.
No disadvantage aside from it making tuples indistinguishable from lists.
No, they'd still have statically known length and be heterogenous, it would just change some strictness properties. Ganesh

Tuples would still be distinguishable from lists, since "cons" changes their type: (b,c,d) and (a,b,c,d) would have different types, while [b,c,d] and [a,b,c,d] wouldn't. On 30 Nov 2008, at 20:48, Brandon S. Allbery KF8NH wrote:
On 2008 Nov 30, at 12:43, Max Rabkin wrote:
On Sun, Nov 30, 2008 at 9:30 AM, Luke Palmer
wrote: cross :: [a] -> [b] -> [(a,b)]
It's just kind of a pain (you build [(a,(b,(c,d)))] and then flatten out the tuples). The applicative notation is a neat little trick which does this work for you.
It seems to me like this would all be easy if (a,b,c,d) was sugar for (a,(b,(c,d))), and I can't see a disadvantage to that.
No disadvantage aside from it making tuples indistinguishable from lists.
-- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Nov 30, 2008 at 10:43 AM, Max Rabkin
On Sun, Nov 30, 2008 at 9:30 AM, Luke Palmer
wrote: cross :: [a] -> [b] -> [(a,b)]
It's just kind of a pain (you build [(a,(b,(c,d)))] and then flatten out the tuples). The applicative notation is a neat little trick which does this work for you.
It seems to me like this would all be easy if (a,b,c,d) was sugar for (a,(b,(c,d))), and I can't see a disadvantage to that.
This is a tricky and subtle question, actually. It has to do with the lifting of tuples; those two types have different domains. For example, the element in the latter: (1,(2,_|_)) Has no corresponding element in the former (there is (1,2,_|_,_|_), but that corresponds to (1,(2,(_|_,_|_))) ). Now, if tuples in Haskell were unlifted, meaning (_|_,_|_) = _|_, then there would be no issue. But that has far-reaching consequences in the language design, among which the "seq" function would have to be eliminated (many people would not be opposed to this). Also usage of unlifted tuples can cause subtle space leaks. Now, what all this domain theory has to do with practical issues, I'm not sure. But you can't just do a slick replacement, because it changes properties of programs that did not know the difference. Frankly, I would prefer what you propose as well (actually, I would prefer it to mean (a,(b,(c,(d,())))), but it's the same idea). But the change is difficult and requires thought. Luke

You can have seq and lifted tuples, but the implementation of seq
requires parallel evaluation.
-- Lennart
On Sun, Nov 30, 2008 at 7:00 PM, Luke Palmer
On Sun, Nov 30, 2008 at 10:43 AM, Max Rabkin
wrote: On Sun, Nov 30, 2008 at 9:30 AM, Luke Palmer
wrote: cross :: [a] -> [b] -> [(a,b)]
It's just kind of a pain (you build [(a,(b,(c,d)))] and then flatten out the tuples). The applicative notation is a neat little trick which does this work for you.
It seems to me like this would all be easy if (a,b,c,d) was sugar for (a,(b,(c,d))), and I can't see a disadvantage to that.
This is a tricky and subtle question, actually. It has to do with the lifting of tuples; those two types have different domains. For example, the element in the latter:
(1,(2,_|_))
Has no corresponding element in the former (there is (1,2,_|_,_|_), but that corresponds to (1,(2,(_|_,_|_))) ).
Now, if tuples in Haskell were unlifted, meaning (_|_,_|_) = _|_, then there would be no issue. But that has far-reaching consequences in the language design, among which the "seq" function would have to be eliminated (many people would not be opposed to this). Also usage of unlifted tuples can cause subtle space leaks.
Now, what all this domain theory has to do with practical issues, I'm not sure. But you can't just do a slick replacement, because it changes properties of programs that did not know the difference.
Frankly, I would prefer what you propose as well (actually, I would prefer it to mean (a,(b,(c,(d,())))), but it's the same idea). But the change is difficult and requires thought.
Luke _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 11/30/08 11:30, Luke Palmer wrote:
On Sun, Nov 30, 2008 at 10:25 AM, Larry Evans
wrote: Is there some version of haskell, maybe template haskell, that can do that, i.e. instead of:
cross::[[a]] -> [[a]]
have:
crossn::[a0]->[a1]->...->[an] -> [(a0,a1,...,an)]
Ah yes! This is straightforward usage of the list monad. I suggest applicative notation:
import Control.Applicative (,,,) <$> xs0 <*> xs1 <*> xs2 <*> xs3
Or alternatively:
import Control.Monad liftM4 (,,,) xs0 xs1 xs2 xs3
(I would have used liftA4, but it's not defined. The definition looks a lot like the first example :-)
This notation seems a bit magical, but you can build what you want using a simple binary cross:
cross :: [a] -> [b] -> [(a,b)]
It's just kind of a pain (you build [(a,(b,(c,d)))] and then flatten out the tuples). The applicative notation is a neat little trick which does this work for you.
Thanks Luke. I'll try that.
If you're asking whether crossn, as a single function which handles arbitrarily many arguments, can be defined, the short answer is "no". I dare you to come up with a case in which such function adds more than cursory convenience.
The following post: http://thread.gmane.org/gmane.comp.lib.boost.devel/182797 shows at least one person that would find it useful, at least in c++. Of course maybe it would be less useful in haskell.

On 11/30/08 12:04, Larry Evans wrote: [snip]
The following post:
http://thread.gmane.org/gmane.comp.lib.boost.devel/182797
shows at least one person that would find it useful, at least in c++. Of course maybe it would be less useful in haskell.
One thing that maybe confusing things is that the c++ template code calculated a crossproduct of types, not values. The haskell code: cross::[[a]]->[[a]] calculate a cross product of values. Sorry if that was unclear. I was trying to use haskell to guide me in doing something similar with c++ template metaprogramming.

Larry Evans wrote:
The haskell code:
cross::[[a]]->[[a]]
calculate a cross product of values.
Now if you allow the elements of that function's argument list to be possibly infinite lists and you still want to eventually yield every possible cross product, you get a very nice problem... Martijn.

On Sun, Nov 30, 2008 at 2:07 PM, Martijn van Steenbergen
Larry Evans wrote:
The haskell code:
cross::[[a]]->[[a]]
calculate a cross product of values.
Now if you allow the elements of that function's argument list to be possibly infinite lists and you still want to eventually yield every possible cross product, you get a very nice problem...
Solved by control-monad-omega (not really a monad). The other nice one problem is allowing the argument itself to be infinite (you have to require all of the lists to be nonempty). Luke

Luke Palmer wrote:
The other nice one problem is allowing the argument itself to be infinite (you have to require all of the lists to be nonempty).
I think the requirement has to be a lot stronger for that to work. If every sublist has two elements, the answer is 2^infinity lists which is uncountable. In order for the answer to be countable, you have to require that only a finite number of sublists contain more than one element, at which point you can use your omega monad again. Martijn.

On Sun, Nov 30, 2008 at 3:13 PM, Martijn van Steenbergen
Luke Palmer wrote:
The other nice one problem is allowing the argument itself to be infinite (you have to require all of the lists to be nonempty).
I think the requirement has to be a lot stronger for that to work.
If every sublist has two elements, the answer is 2^infinity lists which is uncountable.
Good catch. If there are infinitely many finite lists, you can construct a searchable set of results: import Data.Searchable -- from infinite-search finiteList :: [a] -> Set a finiteList = foldr1 union . map singleton cross :: Eq a => [[a]] -> Set a cross = sequence . map finiteList ghci> let cantor = cross (repeat [True,False]) ghci> fmap (take 10) $ search cantor $ \xs -> not (any (xs !!) [3..6]) Just [True,True,True,False,False,False,False,True,True,True] Which is pretty much unrelated to what we were talking about. But it's cool to show of Martin Escardo's neat stuff. Luke

On Sun, Nov 30, 2008 at 11:04 AM, Larry Evans
The following post:
http://thread.gmane.org/gmane.comp.lib.boost.devel/182797
shows at least one person that would find it useful, at least in c++. Of course maybe it would be less useful in haskell.
The line:
typedef boost::mpl::vector

On 11/30/08 12:27, Luke Palmer wrote:
On Sun, Nov 30, 2008 at 11:04 AM, Larry Evans
wrote: The following post:
http://thread.gmane.org/gmane.comp.lib.boost.devel/182797
shows at least one person that would find it useful, at least in c++. Of course maybe it would be less useful in haskell.
The line:
typedef boost::mpl::vector
TT; Has the number of lists hard-coded as 3, and does not abstract over it. This corresponds to the "3" in "liftA3", or the number of <*>s in the expression.
Abstracting over the number and types of arguments is something neither C++ nor Haskell is very good at. But in order to be able to do any abstraction using such a variable-argument function, the type systems of these languages would have to increase in complexity by quite a lot.
Luke
True, but if you look at the cross_nproduct_view template: {--cut here-- template < class Domains
struct
cross_nproduct_view
: fold
< Domains
, cross_product_one
, cross_product_view

On 11/30/08 12:49, Larry Evans wrote: [snip]
You'll see Domains can be an mpl::vector of any length. The cross_nproduct_view_test.cpp tests with a 3 element Domains:
typedef mpl::vector < mpl::range_c
, mpl::range_c , mpl::range_c > domains;
OOPS. That's in another test driver. The one
in the cross_nproduct_view_test.cpp has:
typedef range_c
The cross_nproduct_view template and test driver are found in the cross_nproduct_view.zip file here:

Am Sonntag, 30. November 2008 19:04 schrieb Larry Evans:
If you're asking whether crossn, as a single function which handles arbitrarily many arguments, can be defined, the short answer is "no". I dare you to come up with a case in which such function adds more than cursory convenience.
The following post:
http://thread.gmane.org/gmane.comp.lib.boost.devel/182797
shows at least one person that would find it useful, at least in c++. Of course maybe it would be less useful in haskell.
And having genericCross xs1 xs2 being able to be [(x,y) | x <- xs1, y <- xs2] \xs3 -> cross3 xs1 xs2 xs3 \xs3 xs4 -> cross4 xs1 xs2 xs3 xs4 ... would open up the possibility for a great number of bugs, I believe.
participants (11)
-
Andrea Vezzosi
-
apfelmus
-
Brandon S. Allbery KF8NH
-
Daniel Fischer
-
Ganesh Sittampalam
-
Larry Evans
-
Lennart Augustsson
-
Luke Palmer
-
Martijn van Steenbergen
-
Max Rabkin
-
Miguel Mitrofanov