module Data.InvertibleGrammar.Monad
( module Control.Monad.ContextError
, dive
, step
, locate
, grammarError
, runGrammarMonad
, Propagation
, GrammarError (..)
, Mismatch
, expected
, unexpected
) where
import Control.Applicative
import Control.Monad.ContextError
import Data.Semigroup as Semi
import Data.Set (Set)
import qualified Data.Set as S
import Data.Text (Text)
import Data.Text.Prettyprint.Doc
(Pretty, pretty, vsep, indent, fillSep, punctuate, comma, (<+>))
initPropagation :: p -> Propagation p
initPropagation = Propagation [0]
data Propagation p = Propagation
{ pProp :: [Int]
, pPos :: p
} deriving (Show)
instance Eq (Propagation p) where
Propagation xs _ == Propagation ys _ = xs == ys
instance Ord (Propagation p) where
compare (Propagation as _) (Propagation bs _) =
reverse as `compare` reverse bs
data Mismatch = Mismatch
{ mismatchExpected :: Set Text
, mismatchGot :: Maybe Text
} deriving (Show, Eq)
expected :: Text -> Mismatch
expected a = Mismatch (S.singleton a) Nothing
unexpected :: Text -> Mismatch
unexpected a = Mismatch S.empty (Just a)
instance Semigroup Mismatch where
m <> m' =
Mismatch
(mismatchExpected m Semi.<> mismatchExpected m')
(mismatchGot m <|> mismatchGot m')
instance Monoid Mismatch where
mempty = Mismatch mempty mempty
mappend = (<>)
runGrammarMonad :: p -> (p -> String) -> ContextError (Propagation p) (GrammarError p) a -> Either String a
runGrammarMonad initPos showPos m =
case runContextError m (initPropagation initPos) of
Left (GrammarError p mismatch) ->
Left $ renderMismatch (showPos (pPos p)) mismatch
Right a -> Right a
instance Pretty Mismatch where
pretty (Mismatch (S.toList -> []) Nothing) =
"unknown mismatch occurred"
pretty (Mismatch (S.toList -> expected) got) =
vsep [ ppExpected expected
, ppGot got
]
where
ppExpected [] = mempty
ppExpected xs = "expected:" <+> fillSep (punctuate comma $ map pretty xs)
ppGot Nothing = mempty
ppGot (Just a) = " got:" <+> pretty a
renderMismatch :: String -> Mismatch -> String
renderMismatch pos mismatch =
show $ vsep
[ pretty pos `mappend` ":" <+> "mismatch:"
, indent 2 $ pretty mismatch
]
data GrammarError p = GrammarError (Propagation p) Mismatch
deriving (Show)
instance Semigroup (GrammarError p) where
GrammarError pos m <> GrammarError pos' m'
| pos > pos' = GrammarError pos m
| pos < pos' = GrammarError pos' m'
| otherwise = GrammarError pos (m <> m')
dive :: MonadContextError (Propagation p) e m => m a -> m a
dive =
localContext $ \(Propagation xs pos) ->
Propagation (0 : xs) pos
step :: MonadContextError (Propagation p) e m => m ()
step =
modifyContext $ \propagation ->
propagation
{ pProp = case pProp propagation of
(x : xs) -> succ x : xs
[] -> [0]
}
locate :: MonadContextError (Propagation p) e m => p -> m ()
locate pos =
modifyContext $ \propagation ->
propagation { pPos = pos }
grammarError :: MonadContextError (Propagation p) (GrammarError p) m => Mismatch -> m a
grammarError mismatch =
throwInContext $ \ctx ->
GrammarError ctx mismatch