{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
module Text.Trifecta.Combinators
( DeltaParsing(..)
, sliced
, careting, careted
, spanning, spanned
, fixiting
, MarkParsing(..)
) where
import Control.Applicative
import Control.Monad (MonadPlus)
import Control.Monad.Trans.Class
import Control.Monad.Trans.Identity
import Control.Monad.Trans.Reader
import Control.Monad.Trans.RWS.Lazy as Lazy
import Control.Monad.Trans.RWS.Strict as Strict
import Control.Monad.Trans.State.Lazy as Lazy
import Control.Monad.Trans.State.Strict as Strict
import Control.Monad.Trans.Writer.Lazy as Lazy
import Control.Monad.Trans.Writer.Strict as Strict
import Data.ByteString as Strict hiding (span)
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import Prelude hiding (span)
import Text.Parser.Token
import Text.Trifecta.Delta
import Text.Trifecta.Rendering
class (MonadPlus m, TokenParsing m) => DeltaParsing m where
line :: m ByteString
position :: m Delta
slicedWith :: (a -> Strict.ByteString -> r) -> m a -> m r
rend :: m Rendering
rend = rendered <$> position <*> line
{-# INLINE rend #-}
restOfLine :: m ByteString
restOfLine = Strict.drop . fromIntegral . columnByte <$> position <*> line
{-# INLINE restOfLine #-}
instance (MonadPlus m, DeltaParsing m) => DeltaParsing (Lazy.StateT s m) where
line = lift line
{-# INLINE line #-}
position = lift position
{-# INLINE position #-}
slicedWith f (Lazy.StateT m) = Lazy.StateT $ \s -> slicedWith (\(a,s') b -> (f a b, s')) $ m s
{-# INLINE slicedWith #-}
rend = lift rend
{-# INLINE rend #-}
restOfLine = lift restOfLine
{-# INLINE restOfLine #-}
instance (MonadPlus m, DeltaParsing m) => DeltaParsing (Strict.StateT s m) where
line = lift line
{-# INLINE line #-}
position = lift position
{-# INLINE position #-}
slicedWith f (Strict.StateT m) = Strict.StateT $ \s -> slicedWith (\(a,s') b -> (f a b, s')) $ m s
{-# INLINE slicedWith #-}
rend = lift rend
{-# INLINE rend #-}
restOfLine = lift restOfLine
{-# INLINE restOfLine #-}
instance (MonadPlus m, DeltaParsing m) => DeltaParsing (ReaderT e m) where
line = lift line
{-# INLINE line #-}
position = lift position
{-# INLINE position #-}
slicedWith f (ReaderT m) = ReaderT $ slicedWith f . m
{-# INLINE slicedWith #-}
rend = lift rend
{-# INLINE rend #-}
restOfLine = lift restOfLine
{-# INLINE restOfLine #-}
instance (MonadPlus m, DeltaParsing m, Monoid w) => DeltaParsing (Strict.WriterT w m) where
line = lift line
{-# INLINE line #-}
position = lift position
{-# INLINE position #-}
slicedWith f (Strict.WriterT m) = Strict.WriterT $ slicedWith (\(a,s') b -> (f a b, s')) m
{-# INLINE slicedWith #-}
rend = lift rend
{-# INLINE rend #-}
restOfLine = lift restOfLine
{-# INLINE restOfLine #-}
instance (MonadPlus m, DeltaParsing m, Monoid w) => DeltaParsing (Lazy.WriterT w m) where
line = lift line
{-# INLINE line #-}
position = lift position
{-# INLINE position #-}
slicedWith f (Lazy.WriterT m) = Lazy.WriterT $ slicedWith (\(a,s') b -> (f a b, s')) m
{-# INLINE slicedWith #-}
rend = lift rend
{-# INLINE rend #-}
restOfLine = lift restOfLine
{-# INLINE restOfLine #-}
instance (MonadPlus m, DeltaParsing m, Monoid w) => DeltaParsing (Lazy.RWST r w s m) where
line = lift line
{-# INLINE line #-}
position = lift position
{-# INLINE position #-}
slicedWith f (Lazy.RWST m) = Lazy.RWST $ \r s -> slicedWith (\(a,s',w) b -> (f a b, s',w)) $ m r s
{-# INLINE slicedWith #-}
rend = lift rend
{-# INLINE rend #-}
restOfLine = lift restOfLine
{-# INLINE restOfLine #-}
instance (MonadPlus m, DeltaParsing m, Monoid w) => DeltaParsing (Strict.RWST r w s m) where
line = lift line
{-# INLINE line #-}
position = lift position
{-# INLINE position #-}
slicedWith f (Strict.RWST m) = Strict.RWST $ \r s -> slicedWith (\(a,s',w) b -> (f a b, s',w)) $ m r s
{-# INLINE slicedWith #-}
rend = lift rend
{-# INLINE rend #-}
restOfLine = lift restOfLine
{-# INLINE restOfLine #-}
instance (MonadPlus m, DeltaParsing m) => DeltaParsing (IdentityT m) where
line = lift line
{-# INLINE line #-}
position = lift position
{-# INLINE position #-}
slicedWith f (IdentityT m) = IdentityT $ slicedWith f m
{-# INLINE slicedWith #-}
rend = lift rend
{-# INLINE rend #-}
restOfLine = lift restOfLine
{-# INLINE restOfLine #-}
sliced :: DeltaParsing m => m a -> m ByteString
sliced = slicedWith (\_ bs -> bs)
{-# INLINE sliced #-}
careting :: DeltaParsing m => m Caret
careting = Caret <$> position <*> line
{-# INLINE careting #-}
careted :: DeltaParsing m => m a -> m (Careted a)
careted p = (\m l a -> a :^ Caret m l) <$> position <*> line <*> p
{-# INLINE careted #-}
spanning :: DeltaParsing m => m a -> m Span
spanning p = (\s l e -> Span s e l) <$> position <*> line <*> (p *> position)
{-# INLINE spanning #-}
spanned :: DeltaParsing m => m a -> m (Spanned a)
spanned p = (\s l a e -> a :~ Span s e l) <$> position <*> line <*> p <*> position
{-# INLINE spanned #-}
fixiting :: DeltaParsing m => m Strict.ByteString -> m Fixit
fixiting p = (\(r :~ s) -> Fixit s r) <$> spanned p
{-# INLINE fixiting #-}
class (DeltaParsing m, HasDelta d) => MarkParsing d m | m -> d where
mark :: m d
release :: d -> m ()
instance (MonadPlus m, MarkParsing d m) => MarkParsing d (Lazy.StateT s m) where
mark = lift mark
{-# INLINE mark #-}
release = lift . release
{-# INLINE release #-}
instance (MonadPlus m, MarkParsing d m) => MarkParsing d (Strict.StateT s m) where
mark = lift mark
{-# INLINE mark #-}
release = lift . release
{-# INLINE release #-}
instance (MonadPlus m, MarkParsing d m) => MarkParsing d (ReaderT e m) where
mark = lift mark
{-# INLINE mark #-}
release = lift . release
{-# INLINE release #-}
instance (MonadPlus m, MarkParsing d m, Monoid w) => MarkParsing d (Strict.WriterT w m) where
mark = lift mark
{-# INLINE mark #-}
release = lift . release
{-# INLINE release #-}
instance (MonadPlus m, MarkParsing d m, Monoid w) => MarkParsing d (Lazy.WriterT w m) where
mark = lift mark
{-# INLINE mark #-}
release = lift . release
{-# INLINE release #-}
instance (MonadPlus m, MarkParsing d m, Monoid w) => MarkParsing d (Lazy.RWST r w s m) where
mark = lift mark
{-# INLINE mark #-}
release = lift . release
{-# INLINE release #-}
instance (MonadPlus m, MarkParsing d m, Monoid w) => MarkParsing d (Strict.RWST r w s m) where
mark = lift mark
{-# INLINE mark #-}
release = lift . release
{-# INLINE release #-}
instance (MonadPlus m, MarkParsing d m) => MarkParsing d (IdentityT m) where
mark = lift mark
{-# INLINE mark #-}
release = lift . release
{-# INLINE release #-}