[Haskell-cafe] Selecting Array type

Ryan Ingram ryani.spam at gmail.com
Thu Feb 21 17:15:09 EST 2008


On 2/20/08, Jeff φ <jeff1.61803 at gmail.com> wrote:
> -- SURPRISE 1: If function, arrTypeCast, is removed, (from both
> -- the class and instance) GHC assumes the kind of a and b are *,
> -- instead of * -> * -> * and produce . . .
> --
> -- report3.hs:37:24:
> --     `UArray' is not applied to enough type arguments
> --     Expected kind `*', but `UArray' has kind `* -> * -> *'
> --     In the type `(ArrTypeCast a UArray, IArray a Bool) =>
> --                  SmartArraySelector a Bool'
> --     In the instance declaration for `SmartArraySelector a Bool'
> --
> -- It appears that functions defined in a class can constrain the
> -- type variables of the class.  To me, this seems a bit magical
> -- and unexpected.

That's correct; GHC is doing "kind inference" but defaults to * if it
can't decide otherwise.  Try this instead:
> class ArrTypeCast (a :: * -> * -> *) (b :: * -> * -> *) | a -> b, b->a
> instance ArrTypeCast x x

You can do the same for SmartArraySelector but then you need the
IArray constraint elsewhere; otherwise, smartArray can't call array.

> I'd love to find a good article that describes the ins and outs of multi
> parameter types, functional dependencies, and type assertions, in enough
> detail to resolve these surprises.  A step-by-step walk through showing how
> the compiler resolve a type and selects an instance would be awesome.

Me too.  I don't really know how this code works either :)

It seems like the functional dependency is still broken by ALL of the
declarations; remember that the instance head determines what
instances it defines, and we are specifying that ANY type a can be
specified as SmartArraySelector a Bool, as long as we introduce the
additional constraint of ArrTypeCast a UArray.  This is in contrast to
the functional dependency which states that the element type (Bool)
uniquely determines the array type (some type a?).

Here's an even smaller version of this file, using GHC 6.8.2 and type
equality constraints:

{-# LANGUAGE
    UndecidableInstances, OverlappingInstances,
    MultiParamTypeClasses, FunctionalDependencies,
    FlexibleInstances, TypeFamilies #-}
module SmartArray where
import Data.Array.Unboxed

class IArray a e => SmartArraySelector a e | e -> a
instance a ~ UArray => SmartArraySelector a Bool
instance a ~ UArray => SmartArraySelector a Char
instance a ~ UArray => SmartArraySelector a Double
instance a ~ UArray => SmartArraySelector a Float
instance a ~ UArray => SmartArraySelector a Int
instance a ~ Array  => SmartArraySelector a b

test :: SmartArraySelector a e => e -> a Int e
test e = array (0,10) [ (i,e) | i <- [0..10]]

I wouldn't be surprised if using these features together somehow makes
the type checker inconsistent!

  -- ryan


More information about the Haskell-Cafe mailing list