[Haskell-cafe] Re: Problem with result-type context restrictions in
typeclasses.
DNM
dnmehay at gmail.com
Tue Sep 29 22:48:06 EDT 2009
Correction by the author:
> It seems that ghc doesn't like the fact that I am saying 'foo' must
> return a class 'b' of typeclass 'Bar', while providing a function that
> returns a concrete data instance of 'Bar' (viz., FU or FI) later on
> when I implement 'foo' in each type classes.
Should read:
It seems that ghc doesn't like the fact that I am saying 'foo' must
return something of TYPE 'b' implementing typeclass 'Bar', while
providing
a function that returns a concrete data instance of 'Bar' (viz., FU or
FI)
later on when I implement 'foo' in each type classes.
On Sep 29, 10:43 pm, DNM <dnme... at gmail.com> wrote:
> N.B. I'm a newbie to Haskell, and this problem is a bit complex, so
> bear with me.
>
> I'm using typeclasses to implement a sort of common interface for all
> things -- call them things of type 'Cls' -- that can be expected to
> implement a set of functions -- an 'interface' in OOP-speak. (Yes,
> yes, I'm aware that typeclasses are subtly different and far superior,
> but my Haskell-ese is still a bit rudimentary.)
>
> Essentially, I want to have a typeclass that expects its instances to
> have an accessor function that results in something that is an
> instance of another typeclass whose instances can perform some
> operation. The ghc type-checker doesn't seem to like my code,
> though, and I can't seem to figure out why.
>
> To make it concrete, I've typed up some dummy typeclasses and a dummy
> function that uses their instances to illustrate what I mean, as well
> as the form of the ghc(i) error.
>
> ------------- BEGIN CODE ------------------
> class Cls c where
> foo :: (Bar b) => c -> b
>
> class Bar b where
> toNum :: b -> Int
>
> -- | One implementation of Cls
> data D = D {fu :: FU}
> data FU = FU {num :: Int}
>
> instance Cls D where
> foo = fu
> instance Bar FU where
> toNum f = (num f) + 47
>
> -- | Another implementation of Cls
> data E = E {fi :: FI}
> data FI = FI {nuum :: Int}
>
> instance Cls E where
> foo = fi
> instance Bar FI where
> toNum f = (nuum f) + 100
>
> -- | Yet another (this one re-uses FI)
> data F = F {fii :: FI}
>
> instance Cls F where
> foo = fii
>
> -- | And one last one, just to stress that
> -- I really need to implement multiple
> -- instances of Cls.
> data G = G {fuu :: FU}
>
> instance Cls G where
> foo = fuu
>
> -- | Good. Now, the function 'useThisStuff' need
> -- not know anything about it's payload
> -- other than that it its args are Cls's
> -- (hence they are foo'able things that
> -- can be used to construct an Int answer).
> useThisStuff :: (Cls x, Cls y) => x -> y -> Int
> useThisStuff x y =
> (toNum $ foo x) + (toNum $ foo y)
> ------------- END CODE --------------------
>
> When I type this up in a file and try to load it in ghci, I get the
> following error message(s):
>
> ------------- BEGIN ERROR MSG ----------
> Prelude> :load Typeclasses.hs
> [1 of 1] Compiling Typeclasses ( Typeclasses.hs, interpreted )
>
> Typeclasses.hs:14:10:
> Couldn't match expected type `b' against inferred type `FU'
> `b' is a rigid type variable bound by
> the type signature for `foo' at Typeclasses.hs:4:16
> Expected type: D -> b
> Inferred type: D -> FU
> In the expression: fu
> In the definition of `foo': foo = fu
>
> Typeclasses.hs:23:10:
> Couldn't match expected type `b' against inferred type `FI'
> `b' is a rigid type variable bound by
> the type signature for `foo' at Typeclasses.hs:4:16
> Expected type: E -> b
> Inferred type: E -> FI
> In the expression: fi
> In the definition of `foo': foo = fi
>
> Typeclasses.hs:31:10:
> Couldn't match expected type `b' against inferred type `FI'
> `b' is a rigid type variable bound by
> the type signature for `foo' at Typeclasses.hs:4:16
> Expected type: F -> b
> Inferred type: F -> FI
> In the expression: fii
> In the definition of `foo': foo = fii
>
> Typeclasses.hs:39:10:
> Couldn't match expected type `b' against inferred type `FU'
> `b' is a rigid type variable bound by
> the type signature for `foo' at Typeclasses.hs:4:16
> Expected type: G -> b
> Inferred type: G -> FU
> In the expression: fuu
> In the definition of `foo': foo = fuu
> Failed, modules loaded: none.
> ------------- END ERROR MSG ------------
>
> It seems that ghc doesn't like the fact that I am saying 'foo' must
> return a class 'b' of typeclass 'Bar', while providing a function that
> returns a concrete data instance of 'Bar' (viz., FU or FI) later on
> when I implement 'foo' in each type classes. Repeated for
> convenience:
>
> class Cls c where
> foo :: (Bar b) => c -> b
> ...
> -- (e.g.)
> data G = G {fuu :: FU}
> instance Cls G where
> foo = fuu
>
> Does anyone have any clue as to what I'm doing wrong (language
> extensions that I may need, etc.)?
>
> Is is because I'm using context restrictions on the *result* type of a
> typeclass method? I've written other typeclasses with methods that
> say, essentially:
>
> class A a where
> blah :: (MonadPlus m) => a -> a -> m a
>
> with no issues. The restriction there is not on the return type a, but
> rather on some monadic 'wrapper' around it. This may be why that code
> works.
>
> Please advise. Any help is greatly appreciated.
>
> --D.N. (Dennis)
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-C... at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list