[Haskell-cafe] Re: [Haskell] rigid variables
Robert Dockins
robdockins at fastmail.fm
Thu Jul 20 14:11:34 EDT 2006
[moved to cafe]
On Jul 20, 2006, at 12:48 PM, Rodney D Price wrote:
> I've gotten this sort of error several times, which mysteriously
> disappears
> when I add more functions to the code:
>
> storeError.hs:13:38:
> Couldn't match expected type `a' (a rigid variable)
> against inferred type `String'
> `a' is bound by the type signature for `throwError'
> at <no location info>
> Expected type: a
> Inferred type: String
> In the first argument of `return', namely `msg'
> In the call (return msg)
>
> (This is GHCi.) The code is below. The type variable a can't be
> bound to
> String, obviously, but a relative novice like myself has no idea
> why. Can
> someone tell me?
>
> Thanks,
>
> -Rod
>
> --
> module Store where
>
> import Control.Monad.Error
> import Control.Concurrent.STM
>
> data StoreError = Default String
>
> instance Error StoreError where
> noMsg = Default "Store error"
> strMsg = Default
>
> instance MonadError StoreError STM where
> throwError (Default msg) = return msg
Lets take a look here at the definition of MonadError from
Control.Monad.Error:
class Monad m => MonadError e m | m -> e where
throwError :: e -> m a
catchError :: m a -> (e -> m a) -> m a
In the signature for 'throwError' there are three type variables: e,
m and a. e and m are bound by the instance declaration, but a is
free. In Haskell the rule is that free variables are implicitly
bound with a universal quantifier. So, the type for throwError can
be regarded as,
throwError :: forall a. e -> m a, for some concrete choices of
e and m which are determined by the instance.
The forall means that a user of this function can put any type there
that he likes. In other words, the monadic action created by
'throwError', when executed, evaluates to _a value of any type at
all_ (yes, I know the terminology is a little loose here). That
means you can't just 'return msg', which has type 'm String' because
a user might have used throwError to create an action of type 'm
Int', for example. In fact, you won't really be able to return
anything at all, because there isn't any way to write a program that
can generate a value of any unknown type. This should hopefully
correspond to your intuition about what throwing an exception does.
The error generated by the typechecker basically tells you that the
function you have written is not polymorphic enough. It has type
'StoreError -> STM String' rather than 'forall a. StoreError -> STM
a' as it ought.
I think perhaps you have misunderstood how MonadError is used. The
idea is to expose to users a particular non-local control flow
construct (throw/catch style exceptions) by hiding all the stuff
necessary for that inside the monad plumbing. Usually, whoever
writes the monad itself will provide the necessary instances. It's
often not possible to write instances like this by using the external
API of the monad. This is particularly the case for the abstract
monads available in GHC (IO, ST, and STM).
In short, I don't think you'll be successful in writing a
'MonadError' instance for STM that has the customary semantics. What
you may be looking for is the ErrorT monad transformer, which will
let you layer error handling over STM. It's hard to know with what
info you've provided here. If you give a few more details on what
you're trying to accomplish, someone may be able to give you a push
in the correct direction.
Rob Dockins
Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
-- TMBG
More information about the Haskell-Cafe
mailing list