module Byline.Shell
(
Shell (..),
runShell,
shellHelp,
shellCompletion,
module Byline.Completion,
)
where
import Byline
import Byline.Completion
import qualified Data.Attoparsec.Text as Atto
import Data.Char
import qualified Data.Text as Text
import qualified Options.Applicative as O
import qualified Options.Applicative.Common as O
import qualified Options.Applicative.Types as O
import Relude.Extra.Map
data Shell a = Shell
{
shellPrefs :: O.ParserPrefs,
shellInfo :: O.ParserInfo a,
shellPrompt :: Stylized Text
}
runShell ::
MonadByline m =>
(a -> m ()) ->
Shell a ->
m ()
runShell dispatch Shell {..} = do
input <- askLn shellPrompt Nothing
words <- shellSplit input
unless (null words) (go (map toString words))
where
go words = do
case O.execParserPure shellPrefs shellInfo words of
O.Success a ->
dispatch a
O.Failure help -> do
let str = fst (O.renderFailure help "")
sayLn (text $ toText str)
O.CompletionInvoked _ ->
pure ()
shellHelp ::
MonadByline m =>
Shell a ->
m ()
shellHelp Shell {..} = do
let h = O.parserFailure shellPrefs shellInfo (O.ShowHelpText Nothing) mempty
s = fst (O.renderFailure h "")
sayLn (text $ toText s)
shellCompletion :: Applicative m => Shell a -> CompletionFunc m
shellCompletion shell input@(left, _) = do
if Text.null left || Text.all (isSpace >>> not) left
then completionFromList CompHead (keys commands) input
else completionFromList CompTail flags input
where
flags :: [Text]
flags = fromMaybe [] $ do
cmd <- Text.words left & viaNonEmpty head
names <- lookup cmd commands
pure $
flip map names $ \case
O.OptShort c -> toText ['-', c]
O.OptLong s -> "--" <> toText s
commands :: HashMap Text [O.OptName]
commands =
fromList $
concat $
O.mapParser
(const nameAndFlags)
(O.infoParser $ shellInfo shell)
where
nameAndFlags opt =
case O.optMain opt of
O.CmdReader _ cmds p -> (`map` cmds) $ \cmd ->
( toText cmd,
maybe
[]
( O.infoParser
>>> O.mapParser (const optnames)
>>> concat
)
(p cmd)
)
_ -> mempty
optnames opt =
case O.optMain opt of
O.OptReader ns _ _ -> ns
O.FlagReader ns _ -> ns
_ -> mempty
shellSplit :: MonadByline m => Text -> m [Text]
shellSplit t =
let input = Text.strip t
in if Text.null input
then pure []
else case Atto.parseOnly go input of
Left e -> do
sayLn (("invalid input" <> fg red) <> ": " <> text (toText e))
pure []
Right ws ->
pure ws
where
go :: Atto.Parser [Text]
go = Atto.many1 (bare <|> quoted) <* expectEndOfInput
expectEndOfInput :: Atto.Parser ()
expectEndOfInput = (Atto.endOfInput <|>) $ do
leftover <- Atto.many1 Atto.anyChar
fail ("unexpected input: " <> leftover)
bare :: Atto.Parser Text
bare = (Atto.<?> "unquoted word") $ do
word <- Atto.many1 bareChar
void (Atto.many1 Atto.space) <|> Atto.endOfInput
pure (toText word)
quoted :: Atto.Parser Text
quoted = do
prefix <- many bareChar
quote <- Atto.satisfy (\c -> c == '\'' || c == '"') Atto.<?> "quote"
(_, ScanState {..}) <-
Atto.runScanner (ScanState [] False) (quoteScanner quote)
when scanEscape (fail "expecting a character after a backslash")
_ <- Atto.char quote Atto.<?> "closing quotation character"
let str = toText prefix <> toText (reverse scanResult)
end <-
(Atto.many1 Atto.space $> True)
<|> (Atto.endOfInput $> True)
<|> pure False
if end then pure str else (str <>) <$> quoted
bareChar :: Atto.Parser Char
bareChar = do
char <-
Atto.satisfy
( \c ->
not (isSpace c)
&& c /= '\''
&& c /= '"'
&& isPrint c
)
if char == '\\'
then Atto.anyChar Atto.<?> "escaped character"
else pure char
data ScanState = ScanState
{ scanResult :: [Char],
scanEscape :: Bool
}
quoteScanner ::
Char ->
ScanState ->
Char ->
Maybe ScanState
quoteScanner quote ScanState {..} input
| scanEscape = Just (ScanState (input : scanResult) False)
| input == '\\' = Just (ScanState scanResult True)
| input == quote = Nothing
| otherwise = Just (ScanState (input : scanResult) False)