{-# language BangPatterns #-}
{-# language CPP #-}
{-# language DeriveFoldable #-}
{-# language DeriveFunctor #-}
{-# language DeriveTraversable #-}
{-# language FlexibleContexts #-}
{-# language FlexibleInstances #-}
{-# language FunctionalDependencies #-}
{-# language MultiParamTypeClasses #-}
{-# language Rank2Types #-}
{-# language TemplateHaskell #-}
module Text.Trifecta.Parser
( Parser(..)
, manyAccum
, Step(..)
, feed
, starve
, stepParser
, stepResult
, stepIt
, runParser
, parseFromFile
, parseFromFileEx
, parseString
, parseByteString
, parseTest
) where
import Control.Applicative as Alternative
import Control.Monad (MonadPlus(..), ap, join)
import Control.Monad.IO.Class
import qualified Control.Monad.Fail as Fail
import Data.ByteString as Strict hiding (empty, snoc)
import Data.ByteString.UTF8 as UTF8
import Data.Maybe (fromMaybe, isJust)
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import Data.Semigroup.Reducer
import Data.Set as Set hiding (empty, toList)
import Data.Text.Prettyprint.Doc as Pretty hiding (line)
import System.IO
import Text.Parser.Combinators
import Text.Parser.Char
import Text.Parser.LookAhead
import Text.Parser.Token
import Text.Trifecta.Combinators
import Text.Trifecta.Delta as Delta
import Text.Trifecta.Rendering
import Text.Trifecta.Result
import Text.Trifecta.Rope
import Text.Trifecta.Util.It
import Text.Trifecta.Util.Pretty
newtype Parser a = Parser
{ unparser :: forall r.
(a -> Err -> It Rope r)
-> (Err -> It Rope r)
-> (a -> Set String -> Delta -> ByteString -> It Rope r)
-> (ErrInfo -> It Rope r)
-> Delta
-> ByteString
-> It Rope r
}
instance Functor Parser where
fmap f (Parser m) = Parser $ \ eo ee co -> m (eo . f) ee (co . f)
{-# inlinable fmap #-}
a <$ Parser m = Parser $ \ eo ee co -> m (\_ -> eo a) ee (\_ -> co a)
{-# inlinable (<$) #-}
instance Applicative Parser where
pure a = Parser $ \ eo _ _ _ _ _ -> eo a mempty
{-# inlinable pure #-}
(<*>) = ap
{-# inlinable (<*>) #-}
instance Alternative Parser where
empty = Parser $ \_ ee _ _ _ _ -> ee mempty
{-# inlinable empty #-}
Parser m <|> Parser n = Parser $ \ eo ee co ce d bs ->
m eo (\e -> n (\a e' -> eo a (e <> e')) (\e' -> ee (e <> e')) co ce d bs) co ce d bs
{-# inlinable (<|>) #-}
many p = Prelude.reverse <$> manyAccum (:) p
{-# inlinable many #-}
some p = (:) <$> p <*> Alternative.many p
instance Semigroup a => Semigroup (Parser a) where
(<>) = liftA2 (<>)
{-# inlinable (<>) #-}
instance (Semigroup a, Monoid a) => Monoid (Parser a) where
mappend = (<>)
{-# inlinable mappend #-}
mempty = pure mempty
{-# inlinable mempty #-}
instance Monad Parser where
return = pure
{-# inlinable return #-}
Parser m >>= k = Parser $ \ eo ee co ce d bs ->
m
(\a e -> unparser (k a) (\b e' -> eo b (e <> e')) (\e' -> ee (e <> e')) co ce d bs)
ee
(\a es d' bs' -> unparser (k a)
(\b e' -> co b (es <> _expected e') d' bs')
(\e ->
let errDoc = explain (renderingCaret d' bs') e { _expected = _expected e <> es }
errDelta = _finalDeltas e
in ce $ ErrInfo errDoc (d' : errDelta)
)
co ce
d' bs')
ce d bs
{-# inlinable (>>=) #-}
(>>) = (*>)
{-# inlinable (>>) #-}
#if !(MIN_VERSION_base(4,13,0))
fail = Fail.fail
{-# inlinable fail #-}
#endif
instance Fail.MonadFail Parser where
fail s = Parser $ \ _ ee _ _ _ _ -> ee (failed s)
{-# inlinable fail #-}
instance MonadPlus Parser where
mzero = empty
{-# inlinable mzero #-}
mplus = (<|>)
{-# inlinable mplus #-}
manyAccum :: (a -> [a] -> [a]) -> Parser a -> Parser [a]
manyAccum f (Parser p) = Parser $ \eo _ co ce d bs ->
let walk xs x es d' bs' = p (manyErr d' bs') (\e -> co (f x xs) (_expected e <> es) d' bs') (walk (f x xs)) ce d' bs'
manyErr d' bs' _ e = ce (ErrInfo errDoc [d'])
where errDoc = explain (renderingCaret d' bs') (e <> failed "'many' applied to a parser that accepted an empty string")
in p (manyErr d bs) (eo []) (walk []) ce d bs
liftIt :: It Rope a -> Parser a
liftIt m = Parser $ \ eo _ _ _ _ _ -> do
a <- m
eo a mempty
{-# inlinable liftIt #-}
instance Parsing Parser where
try (Parser m) = Parser $ \ eo ee co _ -> m eo ee co (\_ -> ee mempty)
{-# inlinable try #-}
Parser m <?> nm = Parser $ \ eo ee -> m
(\a e -> eo a (if isJust (_reason e) then e { _expected = Set.singleton nm } else e))
(\e -> ee e { _expected = Set.singleton nm })
{-# inlinable (<?>) #-}
skipMany p = () <$ manyAccum (\_ _ -> []) p
{-# inlinable skipMany #-}
unexpected s = Parser $ \ _ ee _ _ _ _ -> ee $ failed $ "unexpected " ++ s
{-# inlinable unexpected #-}
eof = notFollowedBy anyChar <?> "end of input"
{-# inlinable eof #-}
notFollowedBy p = try (optional p >>= maybe (pure ()) (unexpected . show))
{-# inlinable notFollowedBy #-}
instance Errable Parser where
raiseErr e = Parser $ \ _ ee _ _ _ _ -> ee e
{-# inlinable raiseErr #-}
instance LookAheadParsing Parser where
lookAhead (Parser m) = Parser $ \eo ee _ -> m eo ee (\a _ _ _ -> eo a mempty)
{-# inlinable lookAhead #-}
instance CharParsing Parser where
satisfy f = Parser $ \ _ ee co _ d bs ->
case UTF8.uncons $ Strict.drop (fromIntegral (columnByte d)) bs of
Nothing -> ee (failed "unexpected EOF")
Just (c, xs)
| not (f c) -> ee mempty
| Strict.null xs -> let !ddc = d <> delta c
in join $ fillIt (co c mempty ddc (if c == '\n' then mempty else bs))
(co c mempty)
ddc
| otherwise -> co c mempty (d <> delta c) bs
{-# inlinable satisfy #-}
instance TokenParsing Parser
instance DeltaParsing Parser where
line = Parser $ \eo _ _ _ _ bs -> eo bs mempty
{-# inlinable line #-}
position = Parser $ \eo _ _ _ d _ -> eo d mempty
{-# inlinable position #-}
rend = Parser $ \eo _ _ _ d bs -> eo (rendered d bs) mempty
{-# inlinable rend #-}
slicedWith f p = do
m <- position
a <- p
r <- position
f a <$> liftIt (sliceIt m r)
{-# inlinable slicedWith #-}
instance MarkParsing Delta Parser where
mark = position
{-# inlinable mark #-}
release d' = Parser $ \_ ee co _ d bs -> do
mbs <- rewindIt d'
case mbs of
Just bs' -> co () mempty d' bs'
Nothing
| bytes d' == bytes (rewind d) + fromIntegral (Strict.length bs) -> if near d d'
then co () mempty d' bs
else co () mempty d' mempty
| otherwise -> ee mempty
data Step a
= StepDone !Rope a
| StepFail !Rope ErrInfo
| StepCont !Rope (Result a) (Rope -> Step a)
instance Show a => Show (Step a) where
showsPrec d (StepDone r a) = showParen (d > 10) $
showString "StepDone " . showsPrec 11 r . showChar ' ' . showsPrec 11 a
showsPrec d (StepFail r xs) = showParen (d > 10) $
showString "StepFail " . showsPrec 11 r . showChar ' ' . showsPrec 11 xs
showsPrec d (StepCont r fin _) = showParen (d > 10) $
showString "StepCont " . showsPrec 11 r . showChar ' ' . showsPrec 11 fin . showString " ..."
instance Functor Step where
fmap f (StepDone r a) = StepDone r (f a)
fmap _ (StepFail r xs) = StepFail r xs
fmap f (StepCont r z k) = StepCont r (fmap f z) (fmap f . k)
feed :: Reducer t Rope => t -> Step r -> Step r
feed t (StepDone r a) = StepDone (snoc r t) a
feed t (StepFail r xs) = StepFail (snoc r t) xs
feed t (StepCont r _ k) = k (snoc r t)
{-# inlinable feed #-}
starve :: Step a -> Result a
starve (StepDone _ a) = Success a
starve (StepFail _ xs) = Failure xs
starve (StepCont _ z _) = z
{-# inlinable starve #-}
stepResult :: Rope -> Result a -> Step a
stepResult r (Success a) = StepDone r a
stepResult r (Failure xs) = StepFail r xs
{-# inlinable stepResult #-}
stepIt :: It Rope a -> Step a
stepIt = go mempty where
go r m = case simplifyIt m r of
Pure a -> StepDone r a
It a k -> StepCont r (pure a) $ \r' -> go r' (k r')
{-# inlinable stepIt #-}
data Stepping a
= EO a Err
| EE Err
| CO a (Set String) Delta ByteString
| CE ErrInfo
stepParser
:: Parser a
-> Delta
-> Step a
stepParser (Parser p) d0 = joinStep $ stepIt $ do
bs0 <- fromMaybe mempty <$> rewindIt d0
go bs0 <$> p eo ee co ce d0 bs0
where
eo a e = Pure (EO a e)
ee e = Pure (EE e)
co a es d' bs = Pure (CO a es d' bs)
ce errInf = Pure (CE errInf)
go :: ByteString -> Stepping a -> Result a
go _ (EO a _) = Success a
go bs0 (EE e) = Failure $
let errDoc = explain (renderingCaret d0 bs0) e
in ErrInfo errDoc (d0 : _finalDeltas e)
go _ (CO a _ _ _) = Success a
go _ (CE e) = Failure e
joinStep :: Step (Result a) -> Step a
joinStep (StepDone r (Success a)) = StepDone r a
joinStep (StepDone r (Failure e)) = StepFail r e
joinStep (StepFail r e) = StepFail r e
joinStep (StepCont r a k) = StepCont r (join a) (joinStep <$> k)
{-# inlinable joinStep #-}
runParser
:: Reducer t Rope
=> Parser a
-> Delta
-> t
-> Result a
runParser p d bs = starve $ feed bs $ stepParser p d
{-# inlinable runParser #-}
parseFromFile :: MonadIO m => Parser a -> String -> m (Maybe a)
parseFromFile p fn = do
result <- parseFromFileEx p fn
case result of
Success a -> return (Just a)
Failure xs -> do
liftIO $ renderIO stdout $ renderPretty 0.8 80 $ (_errDoc xs) <> line'
return Nothing
parseFromFileEx :: MonadIO m => Parser a -> String -> m (Result a)
parseFromFileEx p fn = do
s <- liftIO $ Strict.readFile fn
return $ parseByteString p (Directed (UTF8.fromString fn) 0 0 0 0) s
parseByteString
:: Parser a
-> Delta
-> UTF8.ByteString
-> Result a
parseByteString = runParser
parseString
:: Parser a
-> Delta
-> String
-> Result a
parseString = runParser
parseTest :: (MonadIO m, Show a) => Parser a -> String -> m ()
parseTest p s = case parseByteString p mempty (UTF8.fromString s) of
Failure xs -> liftIO $ renderIO stdout $ renderPretty 0.8 80 $ (_errDoc xs) <> line'
Success a -> liftIO (print a)