
I have a program that makes use of various data types built on top of Arrays. In some cases, they're data types that contain an Array plus some additonal information, in others, they're just "newtype" Arrays, so that I can use typechecking to make sure that I'm not using the wrong kind of object. I'd really like to define an "ArrayOps" class with all of the operations I need, and define instances for all of the specific types. I also use some "raw" Array objects, so it would be even better if I could make an instance of my class for Array. And, ideally, I'd like to use the Array operations for my class operations. So, I want something like: class ArrayOps a where (!) :: a -> i -> e (//) :: a -> (i,e) -> a bounds :: a -> (i,i) range :: a -> [i] 'i' and 'e' are the index and element types, respectively. Obviously, the signatures above reference type variables that aren't declared, and really must be constrained to be the 'i' and 'e' that were used in building the type 'a' (which is an Array i e). Something like the following (though this obviously doesn't work): class ((Array.Array i e) a) => ArrayOps a where ... I'm sure there must be a way to do this, but I can't figure out what the syntax would look like. Thanks, Shawn.

You'll probably need to look at associated types/functional dependencies. The former is the new hotness, the latter is the old and not-so-busted. A quick search of the wiki ought to reveal much more than I can possibly explain, there is an example on the page for Assoc. Types about generic Map implementation, which is similar to what you're trying to do. On Oct 31, 2009, at 12:27 PM, Shawn Willden wrote:
I have a program that makes use of various data types built on top of Arrays. In some cases, they're data types that contain an Array plus some additonal information, in others, they're just "newtype" Arrays, so that I can use typechecking to make sure that I'm not using the wrong kind of object.
I'd really like to define an "ArrayOps" class with all of the operations I need, and define instances for all of the specific types. I also use some "raw" Array objects, so it would be even better if I could make an instance of my class for Array. And, ideally, I'd like to use the Array operations for my class operations.
So, I want something like:
class ArrayOps a where (!) :: a -> i -> e (//) :: a -> (i,e) -> a bounds :: a -> (i,i) range :: a -> [i]
'i' and 'e' are the index and element types, respectively.
Obviously, the signatures above reference type variables that aren't declared, and really must be constrained to be the 'i' and 'e' that were used in building the type 'a' (which is an Array i e). Something like the following (though this obviously doesn't work):
class ((Array.Array i e) a) => ArrayOps a where ...
I'm sure there must be a way to do this, but I can't figure out what the syntax would look like.
Thanks,
Shawn. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Am Samstag 31 Oktober 2009 17:33:10 schrieb Joe Fredette:
You'll probably need to look at associated types/functional dependencies. The former is the new hotness, the latter is the old and not-so-busted. A quick search of the wiki ought to reveal much more than I can possibly explain, there is an example on the page for Assoc. Types about generic Map implementation, which is similar to what you're trying to do.
Or perhaps he should look at the class IArray from Data.Array.IArray, maybe he can just declare instances of IArray for his datatypes. Without more information, I can't tell which way to go.
On Oct 31, 2009, at 12:27 PM, Shawn Willden wrote:
I have a program that makes use of various data types built on top of Arrays. In some cases, they're data types that contain an Array plus some additonal information, in others, they're just "newtype" Arrays, so that I can use typechecking to make sure that I'm not using the wrong kind of object.
I'd really like to define an "ArrayOps" class with all of the operations I need, and define instances for all of the specific types. I also use some "raw" Array objects, so it would be even better if I could make an instance of my class for Array. And, ideally, I'd like to use the Array operations for my class operations.
So, I want something like:
class ArrayOps a where (!) :: a -> i -> e (//) :: a -> (i,e) -> a bounds :: a -> (i,i) range :: a -> [i]
'i' and 'e' are the index and element types, respectively.
Obviously, the signatures above reference type variables that aren't declared, and really must be constrained to be the 'i' and 'e' that were used in building the type 'a' (which is an Array i e). Something like the following (though this obviously doesn't work):
class ((Array.Array i e) a) => ArrayOps a where ...
I'm sure there must be a way to do this, but I can't figure out what the syntax would look like.
Thanks,
Shawn.

On Saturday 31 October 2009 10:50:10 am Daniel Fischer wrote:
Am Samstag 31 Oktober 2009 17:33:10 schrieb Joe Fredette:
You'll probably need to look at associated types/functional dependencies. The former is the new hotness, the latter is the old and not-so-busted. A quick search of the wiki ought to reveal much more than I can possibly explain, there is an example on the page for Assoc. Types about generic Map implementation, which is similar to what you're trying to do.
Or perhaps he should look at the class IArray from Data.Array.IArray, maybe he can just declare instances of IArray for his datatypes. Without more information, I can't tell which way to go.
This gives me some ideas, whether to use IArray directly, or just to use it as a model for my own class. Thanks, Shawn.

On Saturday 31 October 2009 10:50:10 am Daniel Fischer wrote:
Or perhaps he should look at the class IArray from Data.Array.IArray, maybe he can just declare instances of IArray for his datatypes. Without more information, I can't tell which way to go.
Looking into the idea of declaring my types as IArray instances, there's one immediate problem: IArray's only method is "bounds". All of the functions that I want as methods of my class are functions in the IArray module (if I'm reading it correctly). So, it seems like what I want to do is to subclass IArray and add the additional methods. Then I can declare instances for my various types and define the methods appropriately. So, I wrote this: ------------------------------------ import Data.Ix (Ix, inRange) import qualified Data.Array.IArray (IArray, Array, array, listArray, range, bounds, (!)) listArray = Data.Array.IArray.listArray array = Data.Array.IArray.array class (Data.Array.IArray.IArray a e) => MyArray a e where bounds :: Ix i => a i e -> (i,i) range :: Ix i => a i e -> [i] (!) :: Ix i => a i e -> i -> e (//) :: Ix i => a i e -> [(i,e)] type Location = (Int, Int) newtype Board = Board (Data.Array.IArray.Array Location Int) instance MyArray Board where bounds = Data.Array.IArray.bounds (!) = (Data.Array.IArray.!) -------------------------------------- However, the instance declaration gives me a "kind mis-match" error. It says that it expects kind '* -> * -> *', but Board has kind '*'. So, I tried: instance MyArray (Board Data.Array.IArray.Array Location Int) where and other variations on that, but they all give me "Board is applied to too many type arguments". How should this be written? Thanks, Shawn.

Well, I think the issue is you're thinking too OOPy... 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) is a type of "kind" * -> * -> *, and if I wanted to implement the IArray class, I would write: instance IArray Foo where ... because IArray is a type-function of type: "(* -> * -> *) -
..." (this is a little stretched, I think, but you get the idea. tl;dr is that "Board" doesn't have enough type arguments to be an IArray. However, I think this is part of a bigger problem.
By way of analogy, consider the Ord class, it implements things like `sort` as derived functions, not as parts of the class. Classes (at least in my estimation) are more like sets of axioms from math than like interfaces from OOP. So one doesn't so much "subclass" something as "add more assumptions" to it. So for instance, I can say, "assume a variable of type `a` which implements the Eq class", then if I want, I can say, "such a variable implements the Ord class if and only if it provides a `compare` or `<=` function". So, while I'm not sure of the specifics of your application and the abilities of IArray. Perhaps it is better to think about how to implement your functions in terms of the `bounds` function. In fact, this is what you do, but I think you're getting caught up in the type-classyness. Saying 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... On Oct 31, 2009, at 10:36 PM, Shawn Willden wrote:
On Saturday 31 October 2009 10:50:10 am Daniel Fischer wrote:
Or perhaps he should look at the class IArray from Data.Array.IArray, maybe he can just declare instances of IArray for his datatypes. Without more information, I can't tell which way to go.
Looking into the idea of declaring my types as IArray instances, there's one immediate problem: IArray's only method is "bounds". All of the functions that I want as methods of my class are functions in the IArray module (if I'm reading it correctly).
So, it seems like what I want to do is to subclass IArray and add the additional methods. Then I can declare instances for my various types and define the methods appropriately.
So, I wrote this:
------------------------------------ import Data.Ix (Ix, inRange) import qualified Data.Array.IArray (IArray, Array, array, listArray, range, bounds, (!))
listArray = Data.Array.IArray.listArray array = Data.Array.IArray.array
class (Data.Array.IArray.IArray a e) => MyArray a e where bounds :: Ix i => a i e -> (i,i) range :: Ix i => a i e -> [i] (!) :: Ix i => a i e -> i -> e (//) :: Ix i => a i e -> [(i,e)]
type Location = (Int, Int) newtype Board = Board (Data.Array.IArray.Array Location Int)
instance MyArray Board where bounds = Data.Array.IArray.bounds (!) = (Data.Array.IArray.!) --------------------------------------
However, the instance declaration gives me a "kind mis-match" error. It says that it expects kind '* -> * -> *', but Board has kind '*'.
So, I tried:
instance MyArray (Board Data.Array.IArray.Array Location Int) where
and other variations on that, but they all give me "Board is applied to too many type arguments".
How should this be written?
Thanks,
Shawn. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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), 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 } 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. 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.

Ahh, I see what you need, you want to "lift" the IArray functions into your type. Well, Rather than trying to instance the type- you could define your type like this: newtype Board = Board IArray.IArray ... whatever (!) :: Board -> Location -> Int (!) = IArray.(!) That is, create synonyms manually for each function you _absolutely need, assuming they don't conflict elsewhere. You would have to manually import each -- I feel like there is probably a better way to do this, but this will definitely work. Though, I'm not sure why you'd need to be instancing another class with a type like this, it's a _very_ specific type, I imagine one or the other set of functions ought to be easy enough to define simply about the type (dodging the typeclass entirely). I imagine extensibility comes to play here. One thing you might be able to do is class IArray a Location Int , OtherClass a ... => MyClass a ... where Which would force you to have a type which is an IArray of Location -> Ints, and an OtherClass, etc. I don't know all the details of your implementation, so I don't know how well this would work, but I imagine thats probably the "better" solution I'm thinking of... /Joe On Oct 31, 2009, at 11:42 PM, Shawn Willden wrote:
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), 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 }
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.
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.

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.

On Saturday 31 October 2009 10:33:10 am Joe Fredette wrote:
You'll probably need to look at associated types/functional dependencies. The former is the new hotness, the latter is the old and not-so-busted. A quick search of the wiki ought to reveal much more than I can possibly explain, there is an example on the page for Assoc. Types about generic Map implementation, which is similar to what you're trying to do.
Hmm. That looks like it will require a deeper dive into the theory than I want to make right now. I don't yet understand what a kind is yet, much less how to write an appropriate kind signature. It appears to be a somewhat disconcerting fact that learning Haskell requires reading original research papers on type theory and lambda calculus. I suppose I need to get over my reluctance and dive into some of that -- but I lack the big slabs of time needed to immerse myself in it enough to make useful progress. Learning Haskell appears to be something one should do as a college student :-) Shawn.
participants (3)
-
Daniel Fischer
-
Joe Fredette
-
Shawn Willden