[Haskell-cafe] Re: kinds question

Ashley Yakeley ashley at semantic.org
Sun Dec 25 00:46:09 EST 2005


In article <20051223143950.GA31551 at abridgegame.org>,
 David Roundy <droundy at abridgegame.org> wrote:

> On Thu, Dec 22, 2005 at 06:27:41PM -0800, Ashley Yakeley wrote:
> > David Roundy wrote:
> > >Hello all,
> > >
> > >I have a question about how to create the right kind to declare lists to be
> > >a class.  I have a class Foo
> > >
> > >class Foo f where
> > >  foo :: f a -> Foo
> > >
> > >and I want to define that a list of Foos is also a Foo, but can't see how
> > >to do it.  I imagine something like
> > >
> > >instance Foo f => Foo [f] where
> > >  foo xs = map foo xs
> > >
> > >but of course [f] isn't a valid type.
> > 
> > [] and f both have * -> *, and you want to compose them. You can do this 
> > like this:
> > 
> >   newtype Compose p q a = MkCompose p (q a)
> > 
> > and then
> > 
> >   instance Foo f => instance (Compose [] f) where
> >     foo (MkCompose fs) = ...
> 
> Given:
> 
> instance Foo f => Foo (Compose [] f) where
>     foo _ = undefined
> 
> ghc gives me the error:
> 
> test.hs:24:0:
>     Illegal instance declaration for `Foo (Compose [] f)'
>         (The instance type must be of form (T a b c)
>          where T is not a synonym, and a,b,c are distinct type variables)
>     In the instance declaration for `Foo (Compose ([]) f)'

Oh, you need -fglasgow-exts.

> I can, however, define
> 
> instance (Functor p, Foo q) => Foo (Compose p q) where
>     foo (MkCompose fs) = MkCompose (fmap foo fs)
> 
> but in any case, this doesn't make a list itself a Foo, so you'd still need
> wrappers, which would defeat the point of putting lists into the class.  :(

Your problem is that you want to apply function "foo" to something of 
type "[f a]". But foo has type "f' a -> Foo", and "[f a]" and "f' a" 
won't unify. It doesn't matter what else you do with classes and 
instances, you'll have to change the type of one or the other.

-- 
Ashley Yakeley, Seattle WA



More information about the Haskell-Cafe mailing list