Parallel list comprehensions
Cale Gibbard
cgibbard at gmail.com
Sat Feb 4 16:08:42 EST 2006
cartesian xs ys = map (\[x,y] -> (x,y)) $ sequence [xs,ys]
On 04/02/06, Jan-Willem Maessen <jmaessen at alum.mit.edu> wrote:
>
> On Feb 4, 2006, at 1:31 PM, Jon Fairbairn wrote:
> > ...
> > There ought to be a list_product somewhere (I mean [1..]
> > `list_product` [4..] ==
> > [(1,4),(2,4),(1,5),(3,4),(2,5),(1,6),...]). Is there?
>
> Not that I know of, but here's one which handles finite lists
> correctly; it'd be a nice addition to Data.List:
>
> dzip :: [a] -> [b] -> [(a,b)]
> dzip = dzipWith (,)
>
> dzipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
> dzipWith f [] ys = []
> dzipWith f as [] = []
> dzipWith f as (y:ys) = dzipK ys [y]
> where dzipK (b:bs) rbs =
> zipWith f as rbs ++ dzipK bs (b : rbs)
> dzipK [] rbs = dzipT as
> where dzipT ys@(_:yt) = zipWith f ys rbs ++ dzipT yt
> dzipT [] = []
>
> -Jan-Willem Maessen
>
> >
> > Jón
> >
> > --
> > Jón Fairbairn Jon.Fairbairn at
> > cl.cam.ac.uk
> >
> >
> > _______________________________________________
> > Haskell-prime mailing list
> > Haskell-prime at haskell.org
> > http://haskell.org/mailman/listinfo/haskell-prime
>
> _______________________________________________
> Haskell-prime mailing list
> Haskell-prime at haskell.org
> http://haskell.org/mailman/listinfo/haskell-prime
>
More information about the Haskell-prime
mailing list