{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {- | Module : Control.Monad.ErrorX.Class Copyright : (c) Mark Snyder 2008. License : BSD-style Maintainer : Mark Snyder, marks@ittc.ku.edu Stability : experimental Portability : non-portable (multi-parameter type classes) -} module Control.Monad.ErrorX.Class ( ErrorX(..), MonadErrorX(..) ) where import Control.Monad.Index class (Index ix) => ErrorX ix a where noMsgx :: ix -> a strMsgx :: ix -> String -> a noMsgx ix = strMsgx ix "" strMsgx ix _ = noMsgx ix instance (Index ix) => ErrorX ix String where noMsgx (_::ix) = "" strMsgx (_::ix) v = v instance (Index ix) => ErrorX ix IOError where strMsgx (_::ix) = userError class (Monad m, ErrorX ix e, Index ix) => MonadErrorX ix e m | ix m -> e where throwErrorx :: ix -> e -> m a catchErrorx :: ix -> m a -> (e -> m a) -> m a