Control.Monad.Error with a custom error type

I have:
data Reference = Ref [String] String data ReferenceError = RefError { expectedType :: String -- type of element we were looking for (e.g. "type","package") , pointOfError :: Reference -- path to deepest parent element not found in path } type ReferenceMonad = Either ReferenceError
I want to write functions that use "Either ReferenceError a" as as the error monad, instead of the more common "Either String a". In particular, I want to use be able to write:
type Model = [(String,Type)] findType :: Model -> Reference -> ReferenceMonad Type findType m -> r@(Ref [] name) = case lookup ((==name) . nameOf) m of Nothing -> throwError r Just x -> return x
I know that I could make this work by making ReferenceError an instance of the Error class, but I cannot provide meaningful implementations of "noMsg" and "strMsg" for ReferenceError. So, it seems instead I need to make (Either ReferenceError) an instance of MonadError. However, when I try, I get:
instance MonadError (Either ReferenceError)
Kind error: `Either ReferenceError' is not applied to enough type arguments When checking kinds in `MonadError (Either ReferenceError)' In the instance declaration for `MonadError (Either ReferenceError)' So, how do I get the effect I want for "findType"? Besides "throwError" I also want to use "catchError". Thanks, Brian (Haskell newbie)

Brian Smith wrote:
[...]
instance MonadError (Either ReferenceError)
Kind error: `Either ReferenceError' is not applied to enough type arguments When checking kinds in `MonadError (Either ReferenceError)' In the instance declaration for `MonadError (Either ReferenceError)'
MonadError takes two parameters: the error type (with kind *) and the monad (with kind *->*). So: instance MonadError ReferenceError (Either ReferenceError) Unfortunately this takes you into the realm of Overlapping Instances. I recommend that you instead extend ReferenceError so that it /can/ be made an instance of Error: data ReferenceError = {- what you already had -} | NonRefError String ...and bear in mind that NonRefError will only occur when the fail method or the mzero method is used, which won't happen much if you consistently use throwError instead. It sometimes helps to define a function which catches one sort of error and lets others through: -- untested m `onRefError` h = m `catchError` \e -> case e of RefError{} -> h (expectedType e) (pointOfError e) _ -> throwError e HTH. Tom
participants (2)
-
Brian Smith
-
Tom Pledger