Hi Paul,

I don't have time to solve your actual problem, but I think it's doable using associated type families. I attach a module which I'm using in my current project that does things quite similar to what you're asking for.

For example:

  *Main> replicateArray (3 :> IntArr) 4
  [4,4,4]

  *Main> replicateArray (4 :> 3 :> IntArr) 4
  [[4,4,4],[4,4,4],[4,4,4],[4,4,4]]

Hope it helps!

/ Emil



Paul Keir skrev:
Hi all,

If I have a list, and I'd like to convert it to a list of lists,
each of length n, I can use a function like bunch:

bunch _ [] = []
bunch n as = let (c,cs) = splitAt n as in c:bunch n cs

 > bunch 8 [1..16]
[[1,2,3,4,5,6,7,8],[9,10,11,12,13,14,15,16]]

If I now want to do the same for the nested lists, I can compose
an application involving both map and bunch:

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

and I can "bunch" the new length 4 lists again:

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

Clearly there is a pattern here involving the bunch function and
latterly, three Int parameters; 2, 4 and 8. My question is, can I
create a function that will take such parameters as a list, and
give the same result, for example:

 > f [2,4,8] [1..16]
[[[[1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16]]]]

or perhaps:

 > f [bunch 2, bunch 4, bunch 8] [1..16]
[[[[1,2],[3,4]],[[5,6],[7,8]]],[[[9,10],[11,12]],[[13,14],[15,16]]]]

I think it may not be possible because the type signature of f would
depend on the length of its list parameter; but I'm not sure.

-Paul


------------------------------------------------------------------------

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
{-# LANGUAGE TypeFamilies #-}

class Storable a
  where
    data Dimension a
    type Element a

    listDimensions :: Dimension a -> [Int]
    replicateArray :: Dimension a -> Element a -> a
    makeSquare     :: Dimension a -> Element a -> a -> a

instance Storable Bool
  where
    data Dimension Bool = BoolArr
    type Element   Bool = Bool

    listDimensions BoolArr   = []
    replicateArray BoolArr e = e
    makeSquare BoolArr _     = id

instance Storable Int
  where
    data Dimension Int = IntArr
    type Element   Int = Int

    listDimensions IntArr   = []
    replicateArray IntArr e = e
    makeSquare IntArr _     = id

instance Storable a => Storable [a]
  where
    data Dimension [a] = Int :> Dimension a
    type Element   [a] = Element a

    listDimensions (n :> ns)   = n : listDimensions ns
    replicateArray (n :> ns) a = replicate n (replicateArray ns a)
    makeSquare (n :> ns) a as  = as' ++ replicateArray (diff :> ns) a
      where
        as'  = take n (map (makeSquare ns a) as)
        diff = n - length as'

infixr 5 :>

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to