
First, the IArray class from Data.Array.IArray is not the real thing. Looking at the class in Data.Array.Base, we see {- | Class of immutable array types. An array type has the form @(a i e)@ where @a@ is the array type constructor (kind @* -> * -> *@), @i@ is the index type (a member of the class 'Ix'), and @e@ is the element type. The @IArray@ class is parameterised over both @a@ and @e@, so that instances specialised to certain element types can be defined. -} class IArray a e where -- | Extracts the bounds of an immutable array bounds :: Ix i => a i e -> (i,i) numElements :: Ix i => a i e -> Int unsafeArray :: Ix i => (i,i) -> [(Int, e)] -> a i e unsafeAt :: Ix i => a i e -> Int -> e unsafeReplace :: Ix i => a i e -> [(Int, e)] -> a i e unsafeAccum :: Ix i => (e -> e' -> e) -> a i e -> [(Int, e')] -> a i e unsafeAccumArray :: Ix i => (e -> e' -> e) -> e -> (i,i) -> [(Int, e')] -> a i e unsafeReplace arr ies = runST (unsafeReplaceST arr ies >>= unsafeFreeze) unsafeAccum f arr ies = runST (unsafeAccumST f arr ies >>= unsafeFreeze) unsafeAccumArray f e lu ies = runST (unsafeAccumArrayST f e lu ies >>= unsafeFreeze) That's more like it, isn't it? Doesn't solve your kind problems, though. Am Sonntag 01 November 2009 04:42:24 schrieb Shawn Willden:
On Saturday 31 October 2009 08:55:56 pm Joe Fredette wrote:
Well, I think the issue is you're thinking too OOPy...
I understand what you're saying, but I don't think I am.
But let me answer the actual problem first, type classes are (basically) functions on types. So a type of "kind" `* -> * -> *` means it is a type which accepts two type variables. So:
newtype Foo a b = Foo (a, b)
Okay, that makes sense. What I'd read about kinds was considerably less clear. Thanks.
newtype Board = Board IArray ...
means that _you can just use the IArray types_! Well, almost, really what you want is a type-synonym:
type Board = IArray Location ...
Now you can write functions like
foo :: Board -> Int foo = Board !! (1,2)
and it will "just work" because Board _is_ an "IArray".
Hope that makes sense...
It does make sense, but it doesn't solve my problem. See, Board isn't the only type I have (and, also, Board has to be a newtype rather than a type synonym because it's also an instance of another class -- well, unless I want to turn on the extension that allows instances of synonyms, and I'm not sure what the etiquette is there),
That's not much of a problem. It may not be portable (maybe it is, maybe not, I don't know), but it's nothing unsafe. Or you could use FlexibleInstances and instance OtherClass (Array Location Int) where...
and some of the others aren't just IArrays with an aliased name, they have other data elements as well. For example:
data ScoredBoard = ScoredBoard { arry :: (IArray Location String) score :: Int maxScore :: Int }
Would something like import Data.Array.Base data ScoreBoard i e = ScoreBoard { arry :: Array i e , score :: Int , maxScore :: Int } instance IArray ScoreBoard e where bounds sb = bounds (arry sb) numElements sb = numElements (arry sb) unsafeArray bds ass = ScoreBoard (unsafeArray bds ass) 0 0 unsafeAt sb i = unsafeAt (arry sb) i ... be an option (analogous for Board)?
I would like to be able to use (!), (//), bound, range, etc., on those as well, and without having to say "range (arry sb)", or having to define a bunch of fooRange, barRange, bazRange, etc., functions.
If you don't want to change the kind of Board etc, another option would be a multiparameter type class with functional dependencies or type families: With fundeps: class KindOfArrayLike a i e | a -> i, a -> e where (!) :: a -> i -> e (//) :: a -> [(i,e)] -> a ... instance KindOfArrayLike Board Location Int where (Board a) ! i = a Data.Array.IArray.! i (Board a) // upd = Board (a Data.Array.IArray.// upd) ... instance KindOfArrayLike ScoreBoard Location String where sb ! i = arry sb Data.Array.IArray.! i sb // upd = sb{ arry = arry sb Data.Array.IArray.// upd } ... With type families: class ArrayLike a where type Idx a :: * type Elt a :: * (!) :: a -> Idx a -> Elt a (//) :: a -> [(Idx a, Elt a)] -> a instance ArrayLike Board where type Idx Board = Location type Elt Board = Int (implementation as before)
Basically I want to take this set of common array operations and overload them for a bunch of different types. As I understand it, classes are effectively the only way to overload in Haskell.
Perhaps it just isn't possible to do what I want? If kind signatures must match, then that's a problem, because different types will have different numbers of construction parameters.
Thanks for the help,
Shawn.