{-# LANGUAGE MultiParamTypeClasses #-}
module Text.Pandoc.Parsing.Capabilities
(
HasIdentifierList (..)
, HasIncludeFiles (..)
, HasLastStrPosition (..)
, updateLastStrPos
, notAfterString
, HasLogMessages (..)
, logMessage
, reportLogMessages
, HasMacros (..)
, QuoteContext (..)
, HasQuoteContext (..)
, failIfInQuoteContext
, HasReaderOptions (..)
, guardEnabled
, guardDisabled
)
where
import Control.Monad (guard, when)
import Data.Text (Text)
import Text.Parsec (SourcePos, Stream, ParsecT,
getPosition, getState, updateState)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Logging (LogMessage)
import Text.Pandoc.Options
( Extension
, ReaderOptions(readerExtensions)
, extensionEnabled
)
import Text.Pandoc.TeX (Macro)
import qualified Data.Map as M
import qualified Data.Set as Set
class HasReaderOptions st where
:: st -> ReaderOptions
getOption :: (Stream s m t) => (ReaderOptions -> b) -> ParsecT s st m b
getOption ReaderOptions -> b
f = ReaderOptions -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall st. HasReaderOptions st => st -> ReaderOptions
extractReaderOptions forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
class HasQuoteContext st m where
getQuoteContext :: (Stream s m t) => ParsecT s st m QuoteContext
withQuoteContext :: QuoteContext -> ParsecT s st m a -> ParsecT s st m a
failIfInQuoteContext :: (HasQuoteContext st m, Stream s m t)
=> QuoteContext
-> ParsecT s st m ()
failIfInQuoteContext :: forall st (m :: * -> *) s t.
(HasQuoteContext st m, Stream s m t) =>
QuoteContext -> ParsecT s st m ()
failIfInQuoteContext QuoteContext
context = do
QuoteContext
context' <- forall st (m :: * -> *) s t.
(HasQuoteContext st m, Stream s m t) =>
ParsecT s st m QuoteContext
getQuoteContext
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (QuoteContext
context' forall a. Eq a => a -> a -> Bool
== QuoteContext
context) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail String
"already inside quotes"
class HasIdentifierList st where
:: st -> Set.Set Text
updateIdentifierList :: (Set.Set Text -> Set.Set Text) -> st -> st
class HasMacros st where
:: st -> M.Map Text Macro
updateMacros :: (M.Map Text Macro -> M.Map Text Macro) -> st -> st
class HasLastStrPosition st where
setLastStrPos :: Maybe SourcePos -> st -> st
getLastStrPos :: st -> Maybe SourcePos
class HasLogMessages st where
addLogMessage :: LogMessage -> st -> st
getLogMessages :: st -> [LogMessage]
class HasIncludeFiles st where
getIncludeFiles :: st -> [Text]
addIncludeFile :: Text -> st -> st
dropLatestIncludeFile :: st -> st
logMessage :: (Stream s m a, HasLogMessages st)
=> LogMessage -> ParsecT s st m ()
logMessage :: forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage LogMessage
msg = forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (forall st. HasLogMessages st => LogMessage -> st -> st
addLogMessage LogMessage
msg)
reportLogMessages :: (PandocMonad m, HasLogMessages st) => ParsecT s st m ()
reportLogMessages :: forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParsecT s st m ()
reportLogMessages = do
[LogMessage]
msgs <- forall st. HasLogMessages st => st -> [LogMessage]
getLogMessages forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report [LogMessage]
msgs
guardEnabled :: (Stream s m a, HasReaderOptions st)
=> Extension -> ParsecT s st m ()
guardEnabled :: forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
ext =
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
getOption ReaderOptions -> Extensions
readerExtensions forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extension -> Extensions -> Bool
extensionEnabled Extension
ext
guardDisabled :: (Stream s m a, HasReaderOptions st)
=> Extension -> ParsecT s st m ()
guardDisabled :: forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
ext =
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
getOption ReaderOptions -> Extensions
readerExtensions forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extension -> Extensions -> Bool
extensionEnabled Extension
ext
updateLastStrPos :: (Stream s m a, HasLastStrPosition st)
=> ParsecT s st m ()
updateLastStrPos :: forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos = forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall st. HasLastStrPosition st => Maybe SourcePos -> st -> st
setLastStrPos forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just
notAfterString :: (Stream s m a, HasLastStrPosition st) => ParsecT s st m Bool
notAfterString :: forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m Bool
notAfterString = do
SourcePos
pos <- forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
st
st <- forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall st. HasLastStrPosition st => st -> Maybe SourcePos
getLastStrPos st
st forall a. Eq a => a -> a -> Bool
/= forall a. a -> Maybe a
Just SourcePos
pos
data QuoteContext
= InSingleQuote
| InDoubleQuote
| NoQuote
deriving (QuoteContext -> QuoteContext -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QuoteContext -> QuoteContext -> Bool
$c/= :: QuoteContext -> QuoteContext -> Bool
== :: QuoteContext -> QuoteContext -> Bool
$c== :: QuoteContext -> QuoteContext -> Bool
Eq, Int -> QuoteContext -> ShowS
[QuoteContext] -> ShowS
QuoteContext -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QuoteContext] -> ShowS
$cshowList :: [QuoteContext] -> ShowS
show :: QuoteContext -> String
$cshow :: QuoteContext -> String
showsPrec :: Int -> QuoteContext -> ShowS
$cshowsPrec :: Int -> QuoteContext -> ShowS
Show)