module System.REPL.Types where
import Control.Exception
import qualified Data.Functor.Apply as Ap
import qualified Data.Functor.Bind as Bi
import qualified Data.Text as T
import Data.Typeable
type TypeError = SomeException
type PredicateError = SomeException
type PromptMsg = T.Text
type Predicate m a b = a -> m (Either PredicateError b)
type Predicate' m a = Predicate m a a
type Parser a = T.Text -> Either TypeError a
data Asker m a b = Asker{
askerPrompt::T.Text,
askerParser::Parser a,
askerPredicate::Predicate m a b}
type Asker' m a = Asker m a a
data SomeREPLError = forall e.Exception e => SomeREPLError e deriving (Typeable)
instance Show SomeREPLError where show (SomeREPLError e) = show e
instance Exception SomeREPLError
replErrorUpcast :: (Exception a) => a -> SomeException
replErrorUpcast = toException . SomeREPLError
replErrorDowncast :: (Exception a) => SomeException -> Maybe a
replErrorDowncast x = do {SomeREPLError y <- fromException x; cast y}
data SomeAskerError = forall e.Exception e => SomeAskerError e deriving (Typeable)
instance Show SomeAskerError where show (SomeAskerError e) = show e
instance Exception SomeAskerError where
toException = replErrorUpcast
fromException = replErrorDowncast
askerErrorUpcast :: (Exception a) => a -> SomeException
askerErrorUpcast = toException . SomeAskerError
askerErrorDowncast :: (Exception a) => SomeException -> Maybe a
askerErrorDowncast x = do {SomeAskerError y <- fromException x; cast y}
data AskerTypeError = AskerTypeError SomeException deriving (Show, Typeable)
instance Exception AskerTypeError where
toException = askerErrorUpcast
fromException = askerErrorDowncast
data AskerPredicateError = AskerPredicateError SomeException deriving (Show, Typeable)
instance Exception AskerPredicateError where
toException = askerErrorUpcast
fromException = askerErrorDowncast
data AskerInputAbortedError = AskerInputAbortedError deriving (Show, Typeable)
instance Exception AskerInputAbortedError where
toException = askerErrorUpcast
fromException = askerErrorDowncast
data GenericTypeError = GenericTypeError T.Text deriving (Show, Typeable, Eq)
instance Exception GenericTypeError
genericTypeError :: T.Text -> SomeException
genericTypeError = SomeException . GenericTypeError
data GenericPredicateError = GenericPredicateError T.Text deriving (Show, Typeable, Eq)
instance Exception GenericPredicateError
genericPredicateError :: T.Text -> SomeException
genericPredicateError = SomeException . GenericPredicateError
newtype Verbatim = Verbatim{fromVerbatim::T.Text}
instance Read Verbatim where
readsPrec _ s = [(Verbatim $ T.pack s,"")]
data PathExistenceType = IsDirectory | IsFile | DoesNotExist deriving (Eq, Show, Ord, Read, Enum, Bounded)
data PathRootDoesNotExist = PathRootDoesNotExist FilePath deriving (Typeable, Eq, Show)
instance Exception PathRootDoesNotExist
data PathIsNotWritable = PathIsNotWritable FilePath deriving (Typeable, Eq, Show)
instance Exception PathIsNotWritable
data SomeCommandError = forall e.Exception e => SomeCommandError e deriving (Typeable)
instance Show SomeCommandError where show (SomeCommandError e) = show e
instance Exception SomeCommandError where
toException = replErrorUpcast
fromException = replErrorDowncast
commandErrorUpcast :: (Exception a) => a -> SomeException
commandErrorUpcast = toException . SomeCommandError
commandErrorDowncast :: (Exception a) => SomeException -> Maybe a
commandErrorDowncast x = do {SomeCommandError y <- fromException x; cast y}
data MalformedParamsError = MalformedParamsError T.Text deriving (Show, Eq, Typeable, Ord)
instance Exception MalformedParamsError where
toException = commandErrorUpcast
fromException = commandErrorDowncast
data TooManyParamsError = TooManyParamsError Int Int deriving (Show, Eq, Typeable, Ord)
instance Exception TooManyParamsError where
toException = commandErrorUpcast
fromException = commandErrorDowncast
data TooFewParamsError = TooFewParamsError Int Int deriving (Show, Eq, Typeable, Ord)
instance Exception TooFewParamsError where
toException = commandErrorUpcast
fromException = commandErrorDowncast
data Command m i a = Command{
commandName :: T.Text,
commandTest :: i -> Bool,
commandDesc :: T.Text,
runPartialCommand :: [i] -> m (a, [i])}
instance Functor m => Functor (Command m i) where
fmap f c@Command{runPartialCommand=run} = c{runPartialCommand=(fmap (\(x,y) -> (f x, y)) . run)}
instance (Monad m) => Ap.Apply (Command m i) where
f <.> g = f{runPartialCommand = h}
where
h input = do (func, output) <- runPartialCommand f input
(arg, output') <- runPartialCommand g output
return (func arg, output')
instance (Monad m) => Bi.Bind (Command m i) where
f >>- g = f{runPartialCommand = h}
where
h input = do (res, output) <- runPartialCommand f input
(res', output') <- runPartialCommand (g res) output
return (res', output')
data NoConfigFileParseError = NoConfigFileParseError T.Text deriving (Show, Eq, Read, Typeable)
instance Exception NoConfigFileParseError