[Haskell-beginners] Multi-param type classes and type dependency

David McBride toad3k at gmail.com
Fri Apr 12 15:39:59 CEST 2013


I don't know if this is the most advisable way to go about things, but if
you add the FunctionalDependencies extension you can do this:

class Collection i c => Annotation i c a | a -> c where

And then it compiles and runs and I assume gives the right answer.


On Fri, Apr 12, 2013 at 8:43 AM, Olivier Iffrig <olivier at iffrig.eu> wrote:

> Hello,
>
> I'm trying to write some code which boils down to this idea : I have a
> collection (Collection), and I want to play with some annotations (of any
> type)
> to the items of the collection.  I will often have only one collection and
> many
> different annotation sets. What matters to me is to be able to have an
> arbitrary index type (or at least instances of Ix) for the collection, and
> use
> it with the annotations as well.
>
> I've come to this code so far :
>
> --------------------
> {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
>
> -- Just for the example
> data Thing = Foo | Bar deriving Show
>
> -- A collection
> -- i is the index type
> -- c is the collection type
> class Collection i c where
>     getThing :: c -> i -> Thing
>
> -- A set of annotations on collection objects
> -- a is an annotation type constructor (a y is an annotation of type y)
> class Collection i c => Annotation i c a where
>     collection :: a y -> c -- access the underlying Collection
>     select :: a y -> i -> y -- select the annotation of an item given its
> index
>
>
> -- My custom collection
> data Things = Things [Thing] deriving Show
>
> -- An annotation set based on a list
> data MyAnnotation c y = Ann c [y]
>
> instance Collection Int Things where
>     getThing (Things ts) i = ts !! i
>
> instance Annotation Int Things (MyAnnotation Things) where
>     collection (Ann c _) = c
>     select (Ann _ as) i =  as !! i
>
> main = print $ select ann (2 :: Int) where
>     ts = Things [Foo, Bar, Foo, Foo]
>     ann = Ann ts ["a", "b", "c", "d"]
> --------------------
>
> This does not work (No instance for (Annotation Int c0 (MyAnnotation
> Things)) arising from a use of `select'). I do not know how I can tell
> the type system that c0 is Things here, if it is actually possible.
>
> I'll appreciate any help or comments on how to rewrite this.
>
> Cheers,
>
> --
> Olivier Iffrig
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130412/fae50f62/attachment.htm>


More information about the Beginners mailing list