[Haskell-beginners] From Functional Dependencies to Type Families

Daniel Fischer daniel.is.fischer at web.de
Thu Dec 3 06:30:08 EST 2009


Am Donnerstag 03 Dezember 2009 04:06:43 schrieb Adolfo Builes:
> > {-# OPTIONS -fglasgow-exts #-}
> >
> > module VarArg where
> > import Data.FiniteMap -- for an example below
> >
> > class BuildList a r | r-> a where
> > build' :: [a] -> a -> r
> >
> > instance BuildList a [a] where
> > build' l x = reverse$ x:l
> >
> > instance BuildList a r => BuildList a (a->r) where
> > build' l x y = build'(x:l) y
> >
> > --build :: forall r a. (BuildList a r) => a -> r
> > build x = build' [] x
>
> I'm trying to replace the code below to work with type families, I started
> out replacing the definition of class with :
>
> class BuildList r where
>     type Build r
>     build' :: [Build r] -> Build r -> r
>
> follow by the instance for [a] resulting in
>
> instance BuildList [a] where
>     type Build [a] = a
>     build' l x = reverse $ x:l
>
> Until here, everything is working, and I'm able to do
>
> > build' [2,3,4] 1 :: [Integer]
> > [4,3,2,1]
>
> then I move on to the next instance (a -> r) with
>
> instance BuildList r => BuildList (a-> r) where
>      type Build (a -> r) =  a
>      build' l x =  \ y -> build'(x:l) y
>
>
> But I get the following error
>
>     Couldn't match expected type `Build r' against inferred type `a'
>       `a' is a rigid type variable bound by
>           the instance declaration at /home/adolfo/foo.hs:347:35
>     In the first argument of `(:)', namely `x'
>     In the first argument of `build'', namely `(x : l)'
>     In the expression: build' (x : l) y
>
> then I try with :
>
> instance BuildList r => BuildList (a-> r) where
>      type Build (a -> r) =  Build r
>      build' l x =  \ y -> build'(x:l) y
>
>
> And I get
>
>       Couldn't match expected type `a' against inferred type `Build r'
>       `a' is a rigid type variable bound by
>           the instance declaration at /home/adolfo/foo.hs:347:35
>       Expected type: [Build r]
>       Inferred type: [Build (a -> r)]
>     In the second argument of `(:)', namely `l'
>     In the first argument of `build'', namely `(x : l)'
>
> I have been trying to figure out, which type should it be, but I haven't
> found the correct one, any ideas ?

I think

instance (BuildList r, Build r ~ a) => BuildList (a -> r) where
    type Build (a -> r) = a
    build' l x = \y -> build' (x:l) y

should work.

You need to tell the compiler explicitly that a and Build r should be the same type.

>
>
> Thanks
>
> -
> Adolfo Builes



More information about the Beginners mailing list