Question

I made a function similar to numpy's array. It converts lists to arrays, lists of lists to 2d arrays, etc.

It works like this:

ghci> arrFromNestedLists ["hello", "world"] :: Array (Int, (Int, ())) Char
array ((0,(0,())),(1,(4,()))) [((0,(0,())),'h'),((0,(1,())),'e'),((0,(2,())),'l'),((0,(3,())),'l'),((0,(4,())),'o'),((1,(0,())),'w'),((1,(1,())),'o'),((1,(2,())),'r'),((1,(3,())),'l'),((1,(4,())),'d')]

(Int, (Int, ())) and not (Int, Int) because I don't know of a programatic way to increase the length of a tuple. (side question: is there such way?)

The coding of it was awkward and I had to do a "workaround" (passing around dummy arguments to functions) for it to work. I wonder if there's a better way.

So here's the code, interrupted with details of the ugly workarounds:

{-# LANGUAGE FlexibleInstances, ScopedTypeVariables, TypeFamilies #-}

type family ListOfIndex i a
type instance ListOfIndex () a = a
type instance ListOfIndex (Int, i) a = [ListOfIndex i a]

class Ix i => ArrConv i where
  acBounds :: a -> ListOfIndex i a -> (i, i)
  acFlatten :: i -> ListOfIndex i a -> [a]

acBounds "should" be :: ListOfIndex i a -> (i, i). And similarly for acFlatten. Each is given a dummy variable (undefined is always the value given) because otherwise I couldn't get it to compile :(

arrFromNestedLists :: forall i a. ArrConv i => ListOfIndex i a -> Array i a
arrFromNestedLists lst =
  listArray
  (acBounds (undefined :: a) lst)
  (acFlatten (undefined :: i) lst)

Above is the dummy undefined argument passing at work. It tells the GHC which instance of ListOfIndex to use.

instance ArrConv () where
  acBounds _ = const ((), ())
  acFlatten _ = (: [])

The below function should have been the acBounds function in an instance of ArrConv, and is declared outside only because I need to use ScopedTypeVariables and I don't know how I can do it in a function in an instance definition..

acSucBounds
  :: forall a i. ArrConv i
  => a -> [ListOfIndex i a] -> ((Int, i), (Int, i))
acSucBounds _ lst =
  ((0, inStart), (length lst - 1, inEnd))
  where
    (inStart, inEnd) = acBounds (undefined :: a) (head lst)

instance ArrConv i => ArrConv (Int, i) where
  acBounds = acSucBounds
  acFlatten _ = concatMap (acFlatten (undefined :: i))
Was it helpful?

Solution

The reason that the extra arguments to acBounds and acFlatten are necessary is that the types a and i cannot be recovered from ListOfIndex i a -> (i, i) and ListOfIndex i a -> [a] respectively. One workaround is to combine the two methods into one method acArgs of type ListOfIndex i a -> ((i, i), a). Now the only problem is to use it in the instance of (Int, i) in a way which prevents the typechecker from generalizing its type too much causing the same problem as before (for example, we cannot simply use fst . acArgs).

{-# LANGUAGE TypeFamilies, FlexibleInstances #-}

import Data.Array

type family ListOfIndex i a
type instance ListOfIndex () a = a
type instance ListOfIndex (Int, i) a = [ListOfIndex i a]

class Ix i => ArrConv i where
  acArgs :: ListOfIndex i a -> ((i, i), [a])

instance ArrConv () where
  acArgs x = (((), ()), [x])

instance ArrConv i => ArrConv (Int, i) where
  acArgs lst =
    (((0, inStart), (length lst - 1, inEnd)), args >>= snd)
    where
      args = map acArgs lst
      (inStart, inEnd) = fst (head args)

arrFromNestedLists :: ArrConv i => ListOfIndex i a -> Array i a
arrFromNestedLists = uncurry listArray . acArgs

OTHER TIPS

If you want to keep acBounds and acFlatten separate, you could add a type-level tag argument to it, i.e. acBounds would have type acBounds :: Proxy a -> ListOfIndex i a -> (i, i). This removes the need for the undefined arguments, since you can just pass (Proxy :: SomeConcreteType) to it; and acBounds has no way of extracting any useful value-level information from it, since it is isomorphic (in an untyped way) to the unit type.

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top