{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FunctionalDependencies #-} -- -- (c) 2012 Wei Ke -- license: GPL-3 -- license-file: LICENSE -- -- | -- The "ErrMsg" module defines the 'ErrMsg' monad for error handling -- in the type checking and the runtime system, -- and some error message operators for convenience. -- module ErrMsg where -- -- monadic ErrMsg -- data ErrMsg a = Err String | OK a instance Monad ErrMsg where Err x >>= _ = Err x OK x >>= f = f x return x = OK x fail x = Err x instance Show a => Show (ErrMsg a) where show (Err x) = "Err# " ++ x show (OK x) = "OK " ++ show x isOK :: ErrMsg a -> Bool isOK (Err _) = False isOK _ = True isErr :: ErrMsg a -> Bool isErr (Err _) = True isErr _ = False infixl 2 ++# (++#) :: ErrMsg a -> String -> ErrMsg a Err x ++# s = Err (x ++ s) x ++# _ = x -- -- converters to ErrMsg -- infixl 2 |? class PlusMsg a b | a -> b where (|?) :: a -> String -> ErrMsg b instance PlusMsg Bool () where False |? s = Err s True |? _ = OK () instance PlusMsg (Maybe a) a where Nothing |? s = Err s Just x |? _ = OK x -- -- constants -- errCtx :: String -> String errCtx s = "\n in " ++ s -- -- end of ErrMsg -- -- --$Id: ErrMsg.hs 1191 2012-11-15 05:13:17Z wke@IPM.EDU.MO $