[Haskell-cafe] Nested Lists

Felipe Lessa felipe.lessa at gmail.com
Thu Jun 4 08:49:48 EDT 2009


How about...

*Main> bunch () [1..16]
[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16]
*Main> bunch (8 :+: ()) [1..16]
[[1,2,3,4,5,6,7,8],[9,10,11,12,13,14,15,16]]
*Main> bunch (8 :+: 4 :+: ()) [1..16]
[[[1,2,3,4],[5,6,7,8]],[[9,10,11,12],[13,14,15,16]]]
*Main> bunch (8 :+: 4 :+: 2 :+: ()) [1..16]
[[[[1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16]]]]



Here's the hack :)

> {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-}
>
> infixr 6 :+:
> data Bunch b = Int :+: b
>
> class Bunchable b a where
>     type Bunched b a :: *
>     bunch :: b -> [a] -> Bunched b a
>
> instance Bunchable () a where
>     type Bunched () a = [a]
>     bunch () = id
>
> instance Bunchable b a => Bunchable (Bunch b) a where
>     type Bunched (Bunch b) a = [Bunched b a]
>     bunch (n :+: r) = map (bunch r) . simpleBunch n
>
> simpleBunch :: Int -> [a] -> [[a]]
> simpleBunch _ [] = []
> simpleBunch n as = let (c,cs) = splitAt n as in c:simpleBunch n cs



The key here is that 'Bunch' reflects its lenght on its type, but
'[]' doesn't.  It may be possible to keep using a list, but it
would be very ugly, I guess.

--
Felipe.


More information about the Haskell-Cafe mailing list