[Haskell-beginners] Class definition syntax

Joe Fredette jfredett at gmail.com
Sat Oct 31 22:55:56 EDT 2009


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 at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



More information about the Beginners mailing list