module System.REPL.Command (
Command(..),
oneOf,
subcommand,
runCommand,
runSingleCommand,
runSingleCommandIf,
makeREPL,
makeREPLSimple,
SomeREPLError(..),
SomeCommandError(..),
MalformedParamsError(..),
TooFewParamsError(..),
TooManyParamsError(..),
readArgs,
getName,
defCommandTest,
quoteArg,
summarizeCommands,
makeCommand,
makeCommand1,
makeCommand2,
makeCommand3,
makeCommand4,
makeCommand5,
makeCommand6,
makeCommand7,
makeCommand8,
makeCommandN,
noOpCmd,
defExitCmd,
defHelpCmd,
defErrorHandler,
) where
import Prelude hiding (putStrLn, putStr, (++), length, replicate)
import qualified Prelude as P
import Control.Monad
import Control.Monad.Catch
import Control.Monad.IO.Class (MonadIO(liftIO))
import Control.Monad.Loops (unfoldrM, iterateUntil)
import Data.Char (isSpace)
import qualified Data.Functor.Bind as Bi
import Data.Functor.Monadic
import qualified Data.List as LU
import qualified Data.List.Safe as L
import Data.ListLike(ListLike(..))
import Data.ListLike.IO (ListLikeIO(..))
import Data.Maybe (fromJust, isJust, fromMaybe)
import Data.Ord
import Data.Typeable (cast)
import qualified Data.Text as T
import System.REPL.Ask
import System.REPL.Types
import qualified System.REPL.Prompt as PR
import qualified Text.Parsec as P
import qualified Text.Parsec.Language as P
import qualified Text.Parsec.Token as P
(++) :: (ListLike full item) => full -> full -> full
(++) = append
runCommand :: (MonadThrow m) => Command m T.Text a -> T.Text -> m a
runCommand c = fmap fst . runPartialCommand c <=< readArgs
runSingleCommand :: (MonadThrow m) => Command m T.Text a -> T.Text -> m a
runSingleCommand c t = fromJust <$> runSingleCommandIf (c{commandTest = const True}) t
runSingleCommandIf :: MonadThrow m => Command m T.Text a -> T.Text -> m (Maybe a)
runSingleCommandIf c t = do
t' <- readArgs t
let t'' = if L.null t' then "" else LU.head t'
if not (commandTest c t'') then return Nothing
else do
(res, output) <- runPartialCommand c t'
let act = max 0 (length t' 1)
mx = act length output
when (not . L.null $ output) (throwM $ TooManyParamsError mx act)
return $ Just res
oneOf :: Monoid i
=> T.Text
-> T.Text
-> [Command m i a]
-> Command m i a
oneOf n d xs = Command n test d cmd
where
test t = L.any (($ t) . commandTest) xs
cmd input = (`runPartialCommand` input)
. LU.head
. L.dropWhile (not . ($ fromMaybe mempty (L.head input)) . commandTest) $ xs
subcommand :: (Monad m, Monoid i)
=> Command m i a
-> [a -> Command m i b]
-> Command m i b
subcommand x xs = x Bi.>>- \y -> oneOf "" "" (L.map ($ y) xs)
readArgs :: MonadThrow m => T.Text -> m [T.Text]
readArgs = either err return . P.parse parser "" . T.unpack
where
err = throwM . MalformedParamsError . T.pack . show
parser = P.many (stringLiteral P.<|> unquotedLiteral)
stringLiteral = P.stringLiteral P.haskell >$> T.pack
unquotedLiteral =
do raw <- P.many1 $ P.satisfy $ not . isSpace
P.eof P.<|> (P.many1 P.space >> return ())
let lit = stringLiteral
res = P.parse lit "" ("\"" ++ raw ++ "\"")
case res of (Right r) -> return r
(Left l) -> fail (show l)
getName :: T.Text -> Maybe T.Text
getName = readArgs >=> L.head
defCommandTest :: [T.Text]
-> T.Text
-> Bool
defCommandTest xs = maybe False (`L.elem` xs) . getName
quoteArg :: T.Text -> T.Text
quoteArg x = if T.null x || T.any isSpace x then '\"' `T.cons` x `T.snoc` '\"'
else x
makeCommand :: (MonadIO m, MonadCatch m, Monoid i)
=> T.Text
-> (i -> Bool)
-> T.Text
-> (i -> m z)
-> Command m i z
makeCommand n t d f = Command n t d f'
where
f' args = do res <- f $ fromMaybe mempty $ L.head args
return (res, L.drop 1 args)
makeCommand1 :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> Asker m a0 a
-> (T.Text -> a -> m z)
-> Command m T.Text z
makeCommand1 n t d canAsk p1 f = Command n t d f'
where
mx = 1
f' args = do let x0 = fromMaybe mempty $ L.head args
when (not canAsk) $ checkParamNum args mx
x1 <- askC p1 args 1
res <- f x0 x1
return (res, L.drop (mx+1) args)
makeCommand2 :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> Asker m a0 a
-> Asker m b0 b
-> (T.Text -> a -> b -> m z)
-> Command m T.Text z
makeCommand2 n t d canAsk p1 p2 f = Command n t d f'
where
mx = 2
f' args = do let x0 = fromMaybe mempty $ L.head args
when (not canAsk) $ checkParamNum args mx
x1 <- askC p1 args 1
x2 <- askC p2 args 2
res <- f x0 x1 x2
return (res, L.drop (mx+1) args)
makeCommand3 :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> Asker m a0 a
-> Asker m b0 b
-> Asker m c0 c
-> (T.Text -> a -> b -> c -> m z)
-> Command m T.Text z
makeCommand3 n t d canAsk p1 p2 p3 f = Command n t d f'
where
mx = 3
f' args = do let x0 = fromMaybe "" $ L.head args
when (not canAsk) $ checkParamNum args mx
x1 <- askC p1 args 1
x2 <- askC p2 args 2
x3 <- askC p3 args 3
res <- f x0 x1 x2 x3
return (res, L.drop (mx+1) args)
makeCommand4 :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> Asker m a0 a
-> Asker m b0 b
-> Asker m c0 c
-> Asker m d0 d
-> (T.Text -> a -> b -> c -> d -> m z)
-> Command m T.Text z
makeCommand4 n t d canAsk p1 p2 p3 p4 f = Command n t d f'
where
mx = 4
f' args = do let x0 = fromMaybe "" $ L.head args
when (not canAsk) $ checkParamNum args mx
x1 <- askC p1 args 1
x2 <- askC p2 args 2
x3 <- askC p3 args 3
x4 <- askC p4 args 4
res <- f x0 x1 x2 x3 x4
return (res, L.drop (mx+1) args)
makeCommand5 :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> Asker m a0 a
-> Asker m b0 b
-> Asker m c0 c
-> Asker m d0 d
-> Asker m e0 e
-> (T.Text -> a -> b -> c -> d -> e -> m z)
-> Command m T.Text z
makeCommand5 n t d canAsk p1 p2 p3 p4 p5 f = Command n t d f'
where
mx = 5
f' args = do let x0 = fromMaybe "" $ L.head args
when (not canAsk) $ checkParamNum args mx
x1 <- askC p1 args 1
x2 <- askC p2 args 2
x3 <- askC p3 args 3
x4 <- askC p4 args 4
x5 <- askC p5 args 5
res <- f x0 x1 x2 x3 x4 x5
return (res, L.drop (mx+1) args)
makeCommand6 :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> Asker m a0 a
-> Asker m b0 b
-> Asker m c0 c
-> Asker m d0 d
-> Asker m e0 e
-> Asker m f0 f
-> (T.Text -> a -> b -> c -> d -> e -> f -> m z)
-> Command m T.Text z
makeCommand6 n t d canAsk p1 p2 p3 p4 p5 p6 f = Command n t d f'
where
mx = 6
f' args = do let x0 = fromMaybe mempty $ L.head args
when (not canAsk) $ checkParamNum args mx
x1 <- askC p1 args 1
x2 <- askC p2 args 2
x3 <- askC p3 args 3
x4 <- askC p4 args 4
x5 <- askC p5 args 5
x6 <- askC p6 args 6
res <- f x0 x1 x2 x3 x4 x5 x6
return (res, L.drop (mx+1) args)
makeCommand7 :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> Asker m a0 a
-> Asker m b0 b
-> Asker m c0 c
-> Asker m d0 d
-> Asker m e0 e
-> Asker m f0 f
-> Asker m g0 g
-> (T.Text -> a -> b -> c -> d -> e -> f -> g -> m z)
-> Command m T.Text z
makeCommand7 n t d canAsk p1 p2 p3 p4 p5 p6 p7 f = Command n t d f'
where
mx = 7
f' args = do let x0 = fromMaybe "" $ L.head args
when (not canAsk) $ checkParamNum args mx
x1 <- askC p1 args 1
x2 <- askC p2 args 2
x3 <- askC p3 args 3
x4 <- askC p4 args 4
x5 <- askC p5 args 5
x6 <- askC p6 args 6
x7 <- askC p7 args 7
res <- f x0 x1 x2 x3 x4 x5 x6 x7
return (res, L.drop (mx+1) args)
makeCommand8 :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> Asker m a0 a
-> Asker m b0 b
-> Asker m c0 c
-> Asker m d0 d
-> Asker m e0 e
-> Asker m f0 f
-> Asker m g0 g
-> Asker m h0 h
-> (T.Text -> a -> b -> c -> d -> e -> f -> g -> h -> m z)
-> Command m T.Text z
makeCommand8 n t d canAsk p1 p2 p3 p4 p5 p6 p7 p8 f = Command n t d f'
where
mx = 8
f' args = do let x0 = fromMaybe "" $ L.head args
when (not canAsk) $ checkParamNum args mx
x1 <- askC p1 args 1
x2 <- askC p2 args 2
x3 <- askC p3 args 3
x4 <- askC p4 args 4
x5 <- askC p5 args 5
x6 <- askC p6 args 6
x7 <- askC p7 args 7
x8 <- askC p8 args 8
res <- f x0 x1 x2 x3 x4 x5 x6 x7 x8
return (res, L.drop (mx+1) args)
makeCommandN :: (MonadIO m, MonadCatch m)
=> T.Text
-> (T.Text -> Bool)
-> T.Text
-> Bool
-> [Asker m a0 a]
-> [Asker m b0 a]
-> (T.Text -> [a] -> m z)
-> Command m T.Text z
makeCommandN n t d canAsk necc opt f = Command n t d f'
where
min = P.length necc
f' args = do when (not canAsk) $ checkParamNum args min
neccParams <- unfoldrM (comb args) (necc,1, Nothing)
let x0 = maybe "" id (L.head args)
from = L.length neccParams + 1
to = Just $ L.length args 1
optParams <- unfoldrM (comb args) (opt, from, to)
let params = neccParams L.++ optParams
res <- f x0 params
return (res, L.drop (length params + 1) args)
comb _ ([],_,_) = return Nothing
comb inp (x:xs, i, j) = if isJust j && fromJust j < i
then return Nothing
else askC x inp i >$> args xs >$> Just
where
args ys y = (y,(ys,i+1,j))
summarizeCommands :: MonadIO m
=> [Command m2 i z]
-> m ()
summarizeCommands [] = return ()
summarizeCommands xs = liftIO $ mapM_ (\c -> prName c >> prDesc c) xs
where
maxLen :: Int
maxLen = fromIntegral
$ T.length
$ commandName
$ fromJust
$ L.minimumBy (comparing $ (* (1)) . T.length . commandName) xs
prName = putStr . padRight ' ' maxLen . commandName
prDesc = putStrLn . (" - " ++) . commandDesc
padRight c i cs = cs ++ replicate (i length cs) c
checkParamNum :: MonadThrow m => [a] -> Int -> m ()
checkParamNum xs need = if have < need then throwM $ TooFewParamsError need have else return ()
where have = max 0 (length xs 1)
askC :: (MonadIO m, MonadCatch m)
=> Asker m a0 a -> [T.Text] -> Int -> m a
askC f xs i = ask f (xs L.!! i)
makeREPL :: (MonadIO m, MonadCatch m)
=> [Command m T.Text a]
-> Command m T.Text b
-> Command m T.Text c
-> m T.Text
-> [Handler m ()]
-> m ()
makeREPL regular exit unknown prompt handlers = void $ iterateUntil id iter
where
iter = (prompt >>= runSingleCommand allCommands)
`catches` handlers'
handlers' = fmap (\(Handler f) -> Handler (\e -> f e >> return False)) handlers
exit' = fmap (const True) exit
regular' = L.map (fmap (const False)) regular
unknown' = fmap (const False) $ unknown{commandTest = const True}
allCommands = oneOf "" "" (exit' : regular' ++ [unknown'])
makeREPLSimple :: (MonadIO m, MonadCatch m)
=> [Command m T.Text a]
-> m ()
makeREPLSimple regular = makeREPL regular defExitCmd unknownCmd PR.prompt defErrorHandler
where
unknownCmd = makeCommandN "" (const True) "" False [] (repeat lineAsker) f
f t ts = if T.all isSpace t && L.all (T.all isSpace) ts
then return ()
else liftIO $ PR.putStrLn $ "Unknown command: " ++ t ++ "."
noOpCmd :: (MonadIO m, MonadCatch m)
=> T.Text
-> [T.Text]
-> Command m T.Text ()
noOpCmd n ns = makeCommand n ((`L.elem` (n:ns)) . T.strip) "" (const $ return ())
defExitCmd :: (MonadIO m, MonadCatch m)
=> Command m T.Text ()
defExitCmd = makeCommand n ((n==) . T.strip) "Exits the program." (const $ return ())
where
n = ":exit"
defHelpCmd :: (MonadIO m, MonadCatch m, Foldable f)
=> f (Command m0 a b)
-> Command m T.Text ()
defHelpCmd cmds = makeCommand n ((n==) . T.strip) "Prints this help text." help
where
n = ":help"
help _ = liftIO $ mapM_ (\x -> putStrLn $ commandName x ++ " - " ++ commandDesc x) cmds
defErrorHandler :: MonadIO m
=> [Handler m ()]
defErrorHandler =
[Handler h_askerGenericTypeError,
Handler h_askerGenericPredicateError,
Handler h_askerPathRootDoesNotExist,
Handler h_askerPathIsNotWritable,
Handler h_tooMalformedParamsError,
Handler h_tooManyParamsError,
Handler h_tooFewParamsError,
Handler h_noConfigFileParseError,
Handler h]
where
put :: String -> IO ()
put = putStrLn
h :: MonadIO m => SomeREPLError -> m ()
h = liftIO . print
h_askerGenericTypeError :: MonadIO m => AskerTypeError -> m ()
h_askerGenericTypeError (AskerTypeError e) = case fromException e of
Just (GenericTypeError t) -> liftIO . put . T.unpack $ t
Nothing -> liftIO . print $ e
h_askerGenericPredicateError :: MonadIO m => AskerPredicateError -> m ()
h_askerGenericPredicateError (AskerPredicateError e) = case fromException e of
Just (GenericPredicateError t) -> liftIO . put . T.unpack $ t
Nothing -> liftIO . print $ e
h_askerPathRootDoesNotExist :: MonadIO m => AskerPredicateError -> m ()
h_askerPathRootDoesNotExist (AskerPredicateError e) = case fromException e of
Just (PathRootDoesNotExist fp) -> liftIO $ put $
"The root of the path '" ++ fp ++
"' does not exist."
Nothing -> liftIO . print $ e
h_askerPathIsNotWritable :: MonadIO m => AskerPredicateError -> m ()
h_askerPathIsNotWritable (AskerPredicateError e) = case fromException e of
Just (PathIsNotWritable fp) -> liftIO $ put $
"The path '" ++ fp ++
"' is not writable."
Nothing -> liftIO . print $ e
h_askerInputAbortedError :: MonadIO m => AskerTypeError -> m ()
h_askerInputAbortedError (AskerTypeError e) =
liftIO $ put "Input aborted."
h_tooMalformedParamsError :: MonadIO m => MalformedParamsError -> m ()
h_tooMalformedParamsError (MalformedParamsError t) = liftIO . put $
"Error parsing parameters: " ++ T.unpack t
h_tooManyParamsError :: MonadIO m => TooManyParamsError -> m ()
h_tooManyParamsError (TooManyParamsError m x) = liftIO . put $
"Expected " ++ exp ++ " parameters, got " ++ got
where
exp = if m > 0
then "at most " ++ show m
else "no"
got = if x <= 0 then "none." else show x ++ "."
h_tooFewParamsError :: MonadIO m => TooFewParamsError -> m ()
h_tooFewParamsError (TooFewParamsError m x) = liftIO . put $
"Expected at least " ++ show m ++ " parameters, got " ++ got
where
got = if x <= 0 then "none." else show x ++ "."
h_noConfigFileParseError :: MonadIO m => NoConfigFileParseError -> m ()
h_noConfigFileParseError (NoConfigFileParseError t) = liftIO . put $
"Error parsing configuration file: " ++ T.unpack t