{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Lang.Crucible.Debug.Statement
( Statement(..)
, ParseError
, renderParseError
, parse
) where
import Data.Text (Text)
import Lang.Crucible.Debug.Command (Command)
import Lang.Crucible.Debug.Command qualified as Cmd
import Data.Text qualified as Text
data Statement cExt
= Statement
{ forall cExt. Statement cExt -> Command cExt
stmtCmd :: Command cExt
, forall cExt. Statement cExt -> [Text]
stmtArgs :: [Text]
}
deriving (forall a b. (a -> b) -> Statement a -> Statement b)
-> (forall a b. a -> Statement b -> Statement a)
-> Functor Statement
forall a b. a -> Statement b -> Statement a
forall a b. (a -> b) -> Statement a -> Statement b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Statement a -> Statement b
fmap :: forall a b. (a -> b) -> Statement a -> Statement b
$c<$ :: forall a b. a -> Statement b -> Statement a
<$ :: forall a b. a -> Statement b -> Statement a
Functor
data ParseError
= InvalidCommand Text
| NoCommand
deriving Int -> ParseError -> ShowS
[ParseError] -> ShowS
ParseError -> String
(Int -> ParseError -> ShowS)
-> (ParseError -> String)
-> ([ParseError] -> ShowS)
-> Show ParseError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParseError -> ShowS
showsPrec :: Int -> ParseError -> ShowS
$cshow :: ParseError -> String
show :: ParseError -> String
$cshowList :: [ParseError] -> ShowS
showList :: [ParseError] -> ShowS
Show
renderParseError :: ParseError -> Text
renderParseError :: ParseError -> Text
renderParseError =
\case
InvalidCommand Text
txt -> Text
"Invalid command: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txt
ParseError
NoCommand -> Text
"No command given"
parse :: Cmd.CommandExt cExt -> Text -> Either ParseError (Statement cExt)
parse :: forall cExt.
CommandExt cExt -> Text -> Either ParseError (Statement cExt)
parse CommandExt cExt
cExts Text
txt =
case Text -> [Text]
Text.words Text
txt of
[] -> ParseError -> Either ParseError (Statement cExt)
forall a b. a -> Either a b
Left ParseError
NoCommand
(Text
cmdText:[Text]
args) ->
case CommandExt cExt -> Text -> Maybe (Command cExt)
forall cExt. CommandExt cExt -> Text -> Maybe (Command cExt)
Cmd.parse CommandExt cExt
cExts Text
cmdText of
Just Command cExt
cmd -> Statement cExt -> Either ParseError (Statement cExt)
forall a b. b -> Either a b
Right (Command cExt -> [Text] -> Statement cExt
forall cExt. Command cExt -> [Text] -> Statement cExt
Statement Command cExt
cmd [Text]
args)
Maybe (Command cExt)
Nothing -> ParseError -> Either ParseError (Statement cExt)
forall a b. a -> Either a b
Left (Text -> ParseError
InvalidCommand Text
cmdText)