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)



_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to