[Haskell-beginners] multi parameter classes and instance
declarations
Daniel Fischer
daniel.is.fischer at web.de
Mon Feb 16 10:17:52 EST 2009
Am Montag, 16. Februar 2009 15:40 schrieb Markus Barenhoff:
> On Mon 16.02 15:28, Markus Barenhoff wrote:
> > Good Afternoon,
> >
> > i'am trying to express something like this here:
> > > -- CI.hs http://pastebin.com/f5b17cf57
> > > {-# OPTIONS -XMultiParamTypeClasses #-}
> > >
> > > module CI(D,f) where
> > >
> > > class B b
> > >
> > > class (B b) => A a b where
> > > f :: b
> > >
> > > data D = D
> > >
> > > instance B D
> > >
> > > instance A D D where
> > > f = D
> > > -- CI.hs
> > >
> > > -- MultiClassTest.hs http://pastebin.com/f1c481e8d
> > > import CI
> > >
> > > a = f
> > > -- MultiClassTest.hs
>
> I forgot to mention that constrain a :: D does leed to the same
> ghc messages.
>
> > ghc output:
> > MultiClassTest.hs:4:4:
> > No instance for (CI.A a D)
> > arising from a use of `f' at MultiClassTest.hs:4:4
> > Possible fix: add an instance declaration for (CI.A a D)
> > In the expression: f
> > In the definition of `a': a = f
> > Failed, modules loaded: CI.
>
GHC doesn't know that there's no other
instance A a D
besides the given instance A D D, so it doesn't know which instance to select
(suppose there were an instance A Bool D where f = undefined, then it's clear
that the instance to use can't be decided).
Since class A is not exported, there can't be without changing CI, so one
might think it would be reasonable to use the only existing instance of A and
be done with it. However, GHC treats type classes with an open world
assumption (i.e. doesn't select instances according to which instances it
currently knows about, but what instances there potentially might be).
To make f usable at all, you must make the type a somehow reachable from f
(e.g. by adding a functional dependency:
{-# LANGUAGE FunctionalDependencies #-}
class (B b) => A a b | b -> a where
f :: b
-- the | b -> a part means that type b uniquely determines type a
)
> Markus
Cheers,
Daniel
More information about the Beginners
mailing list