module System.REPL.Command (
Command(..),
commandInfo,
runOnce,
commandDispatch,
summarizeCommands,
readArgs,
quoteArg,
makeCommand,
makeCommand1,
makeCommand2,
makeCommand3,
makeCommand4,
makeCommand5,
makeCommand6,
makeCommandN,
) where
import Prelude hiding (putStrLn, putStr, getLine, unwords, words, (!!), (++),
length, replicate)
import qualified Prelude as P
import Control.Arrow (left)
import Control.Monad
import Control.Monad.Catch
import Control.Monad.IO.Class (MonadIO(liftIO))
import Control.Monad.Loops (unfoldrM)
import Data.Char (isSpace)
import Data.Functor.Monadic
import qualified Data.List as LU
import qualified Data.List.Safe as L
import Data.ListLike(ListLike(..))
import Data.Maybe (fromJust, isNothing, isJust)
import Data.Ord
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import Data.Typeable
import Numeric.Peano
import System.REPL
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
data Command m a = Command{
commandName :: Text,
commandTest :: Text -> Bool,
commandDesc :: Text,
numParameters :: Maybe Int,
runCommand :: Text -> m a}
instance Functor m => Functor (Command m) where
fmap f c@Command{runCommand=run} = c{runCommand=(fmap f . run)}
data ParamNumError = NoParams | ExactParams | TooManyParams
deriving (Enum, Show, Eq, Read, Typeable, Ord)
instance Exception ParamNumError
commandInfo :: MonadIO m => Command m a -> m ()
commandInfo c = liftIO $ do
putStr $ commandName c
putStrLn $ maybe "" ((" Parameters: " P.++) . show) (numParameters c)
putStrLn $ commandDesc c
readArgs :: Text -> Either Text [Text]
readArgs = (left $ T.pack . show) . P.parse parser "" . T.unpack
where
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)
runOnce :: MonadIO m => Text -> Command m a -> m (Maybe a)
runOnce l c = if commandTest c l then liftM Just (runCommand c l)
else return Nothing
paramErr :: Text
-> [Text]
-> Int
-> Nat
-> ParamNumError
-> Text
paramErr c inp minNum maxNum errType =
"The following " ++ T.pack (show num) ++ " parameters were given to " ++ c ++ ":\n"
++ T.intercalate " " (maybe [] (L.map wrap) $ L.tail inp) ++ ".\n"
++ (numErr LU.!! fromEnum errType)
where
wrap t = if T.any isSpace t then "\"" ++ t ++ "\"" else t
num = L.length inp 1
numErr = [c ++ " takes no parameters.",
c ++ " takes " ++ T.pack (show minNum) ++ " parameters.",
c ++ " takes at most " ++ T.pack (show (fromPeano maxNum :: Integer)) ++ " parameters."]
checkParams :: (MonadIO m, MonadThrow m, Functor m)
=> Text
-> Text
-> Int
-> Nat
-> ([Text] -> m a)
-> m a
checkParams n inp minNum maxNum m =
case readArgs inp of
Left l -> throwM (ParamFailure l)
Right r ->
if natLength r > maxNum + 1 then
throwM $ ParamFailure
$ paramErr n r minNum maxNum (errKind $ natLength r)
else m r
where
errKind len = if minNum == 0 && 0 == maxNum then NoParams
else if maxNum < len then TooManyParams
else ExactParams
quoteArg :: Text -> Text
quoteArg x = if T.null x || T.head x /= '\"'
then '\"' `T.cons` x `T.snoc` '\"'
else x
makeCommand :: (MonadIO m, MonadCatch m,
Functor m)
=> Text
-> (Text -> Bool)
-> Text
-> (Text -> m a)
-> Command m a
makeCommand n t d f =
Command n t d (Just 0) (\inp -> checkParams n inp 0 0 c)
where
c inp = do let li = maybe "" id (L.head inp)
f li
makeCommand1 :: (MonadIO m, MonadCatch m, Functor m, Read a)
=> Text
-> (Text -> Bool)
-> Text
-> Asker m a
-> (Text -> a -> m z)
-> Command m z
makeCommand1 n t d p1 f =
Command n t d (Just 1) (\inp -> checkParams n inp 1 1 c)
where
c inp = do let li = maybe "" id (L.head inp)
x1 <- ask p1 (inp L.!! 1)
f li x1
makeCommand2 :: (MonadIO m, MonadCatch m, Functor m, Read a,
Read b)
=> Text
-> (Text -> Bool)
-> Text
-> Asker m a
-> Asker m b
-> (Text -> a -> b -> m z)
-> Command m z
makeCommand2 n t d p1 p2 f =
Command n t d (Just 2) (\inp -> checkParams n inp 2 2 c)
where
c inp = do let li = maybe "" id (L.head inp)
x1 <- ask p1 (inp L.!! 1)
x2 <- ask p2 (inp L.!! 2)
f li x1 x2
makeCommand3 :: (MonadIO m, MonadCatch m, Functor m, Read a,
Read b, Read c)
=> Text
-> (Text -> Bool)
-> Text
-> Asker m a
-> Asker m b
-> Asker m c
-> (Text -> a -> b -> c -> m z)
-> Command m z
makeCommand3 n t d p1 p2 p3 f =
Command n t d (Just 3) (\inp -> checkParams n inp 3 3 c)
where
c inp = do let li = maybe "" id (L.head inp)
x1 <- ask p1 (inp L.!! 1)
x2 <- ask p2 (inp L.!! 2)
x3 <- ask p3 (inp L.!! 3)
f li x1 x2 x3
makeCommand4 :: (MonadIO m, MonadCatch m, Functor m, Read a,
Read b, Read c, Read d)
=> Text
-> (Text -> Bool)
-> Text
-> Asker m a
-> Asker m b
-> Asker m c
-> Asker m d
-> (Text -> a -> b -> c -> d -> m z)
-> Command m z
makeCommand4 n t d p1 p2 p3 p4 f =
Command n t d (Just 4) (\inp -> checkParams n inp 4 4 c)
where
c inp = do let li = maybe "" id (L.head inp)
x1 <- ask p1 (inp L.!! 1)
x2 <- ask p2 (inp L.!! 2)
x3 <- ask p3 (inp L.!! 3)
x4 <- ask p4 (inp L.!! 4)
f li x1 x2 x3 x4
makeCommand5 :: (MonadIO m, MonadCatch m, Functor m, Read a,
Read b, Read c, Read d, Read e)
=> Text
-> (Text -> Bool)
-> Text
-> Asker m a
-> Asker m b
-> Asker m c
-> Asker m d
-> Asker m e
-> (Text -> a -> b -> c -> d -> e -> m z)
-> Command m z
makeCommand5 n t d p1 p2 p3 p4 p5 f =
Command n t d (Just 4) (\inp -> checkParams n inp 5 5 c)
where
c inp = do let li = maybe "" id (L.head inp)
x1 <- ask p1 (inp L.!! 1)
x2 <- ask p2 (inp L.!! 2)
x3 <- ask p3 (inp L.!! 3)
x4 <- ask p4 (inp L.!! 4)
x5 <- ask p5 (inp L.!! 5)
f li x1 x2 x3 x4 x5
makeCommand6 :: (MonadIO m, MonadCatch m, Functor m, Read a,
Read b, Read c, Read d, Read e, Read f)
=> Text
-> (Text -> Bool)
-> Text
-> Asker m a
-> Asker m b
-> Asker m c
-> Asker m d
-> Asker m e
-> Asker m f
-> (Text -> a -> b -> c -> d -> e -> f -> m z)
-> Command m z
makeCommand6 n t d p1 p2 p3 p4 p5 p6 f =
Command n t d (Just 4) (\inp -> checkParams n inp 6 6 c)
where
c inp = do let li = maybe "" id (L.head inp)
x1 <- ask p1 (inp L.!! 1)
x2 <- ask p2 (inp L.!! 2)
x3 <- ask p3 (inp L.!! 3)
x4 <- ask p4 (inp L.!! 4)
x5 <- ask p5 (inp L.!! 5)
x6 <- ask p6 (inp L.!! 6)
f li x1 x2 x3 x4 x5 x6
makeCommandN :: (MonadIO m, MonadCatch m, Functor m, Read a)
=> Text
-> (Text -> Bool)
-> Text
-> [Asker m a]
-> [Asker m a]
-> (Text -> [a] -> m z)
-> Command m z
makeCommandN n t d necc opt f = Command n t d Nothing (\inp -> checkParams n inp min max c)
where
min = P.length necc
max = natLength necc + natLength opt
c inp = do let li = maybe "" id (L.head inp)
neccParams <- unfoldrM (comb inp) (necc,1, Nothing)
let from = L.length neccParams + 1
to = Just $ L.length inp 1
optParams <- unfoldrM (comb inp) (opt, from, to)
f li (neccParams L.++ optParams)
comb _ ([],_,_) = return Nothing
comb inp (x:xs, i, j) =
if isJust j && fromJust j < i then return Nothing
else ask x (inp L.!! i) >$> args xs >$> Just
where args ys y = (y,(ys,i+1,j))
commandDispatch :: (MonadIO m, MonadCatch m, Functor m)
=> Text
-> [Command m z]
-> m z
commandDispatch input cs =
case readArgs input of
Left l -> throwM (ParamFailure l)
Right input' -> if noMatch input'
then throwM NothingFoundFailure
else do runCommand (fromJust $ first input') input
where
noMatch = isNothing . first
firstArg = maybe "" id . L.head
first r = L.head $ P.dropWhile (not . flip commandTest (firstArg r)) cs
summarizeCommands :: MonadIO m
=> [Command m2 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