{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE Safe #-}
module Base.CompileError (
CompileError(..),
CompileErrorM(..),
) where
#if MIN_VERSION_base(4,8,0)
#else
import Data.Foldable
#endif
#if MIN_VERSION_base(4,13,0)
import Control.Monad.Fail ()
#elif MIN_VERSION_base(4,9,0)
import Control.Monad.Fail
#endif
class CompileError a where
compileError :: String -> a
isCompileError :: a -> Bool
reviseError :: a -> String -> a
reviseError e _ = e
#if MIN_VERSION_base(4,9,0)
class (Functor m, Monad m, MonadFail m) => CompileErrorM m where
#else
class (Functor m, Monad m) => CompileErrorM m where
#endif
compileErrorM :: String -> m a
isCompileErrorM :: m a -> Bool
collectAllOrErrorM :: Foldable f => f (m a) -> m [a]
collectOneOrErrorM :: Foldable f => f (m a) -> m a
reviseErrorM :: m a -> String -> m a
reviseErrorM e _ = e
compileWarningM :: String -> m ()
instance CompileErrorM m => CompileError (m a) where
compileError = compileErrorM
isCompileError = isCompileErrorM
reviseError = reviseErrorM