module Data.Expression.Parser ( Context
, Parser
, Parseable(..)
, parse
, parseWith
, char
, choice
, decimal
, digit
, letter
, many1
, sepBy1
, signed
, space
, string
, identifier
, (<?>)
, assertSort
, assumeSort ) where
import Control.Monad
import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader
import Control.Monad.Trans.State.Lazy
import Data.Map
import Data.Proxy
import Data.Singletons
import Data.Text hiding ( empty )
import Prelude hiding ( lookup )
import Data.Expression.Sort
import Data.Expression.Utils.Indexed.Functor
import Data.Expression.Utils.Indexed.Sum
import qualified Data.Attoparsec.Text as A
type Context = Map String DynamicSort
type Parser = ReaderT Context (StateT Context A.Parser)
class Parseable f g where
parser :: Proxy f -> Parser (DynamicallySorted g) -> Parser (DynamicallySorted g)
parse :: forall f (s :: Sort). ( Parseable f f, SingI s ) => Text -> Maybe (IFix f s)
parse = parseWith empty
parseWith :: forall f (s :: Sort). ( Parseable f f, SingI s ) => Context -> Text -> Maybe (IFix f s)
parseWith c = let a = parser (Proxy :: Proxy f) a in toStaticallySorted <=< A.maybeResult . flip A.feed "" . A.parse (evalStateT (runReaderT a c) empty <* A.endOfInput)
instance (Parseable f h, Parseable g h) => Parseable (f :+: g) h where
parser _ r = A.choice [ parser (Proxy :: Proxy f) r, parser (Proxy :: Proxy g) r ]
char :: Char -> Parser Char
char = lift . lift . A.char
choice :: [Parser a] -> Parser a
choice = A.choice
decimal :: Parser Int
decimal = lift . lift $ A.decimal
digit :: Parser Char
digit = lift . lift $ A.digit
letter :: Parser Char
letter = lift . lift $ A.letter
many1 :: Parser a -> Parser [a]
many1 = A.many1
sepBy1 :: Parser a -> Parser s -> Parser [a]
sepBy1 = A.sepBy1
signed :: Parser Int -> Parser Int
signed m = (*) <$> (lift . lift) (A.signed (pure 1)) <*> m
space :: Parser Char
space = lift . lift $ A.space
string :: Text -> Parser Text
string = lift . lift . A.string
identifier :: Parser String
identifier = (:) <$> id' <*> A.many' (choice [ id', digit ]) where
id' = choice [ letter, char '\'', char '_', char '@', char '#' ]
(<?>) :: Parser a -> String -> Parser a
a <?> l = ReaderT $ \r -> StateT $ \s -> runStateT (runReaderT a r) s A.<?> l
assertSort :: String -> DynamicSort -> Parser ()
assertSort n s = do
ss <- ask
ds <- lift get
case n `lookup` (ss `union` ds) of
Just s' -> when (s /= s') $ fail "sort mismatch"
Nothing -> lift $ modify (insert n s)
assumeSort :: String -> Parser DynamicSort
assumeSort n = do
ss <- ask
ds <- lift get
case n `lookup` (ss `union` ds) of
Just s -> return s
Nothing -> fail "unspecified sort"