{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Parsing.State
( ParserState (..)
, ParserContext (..)
, HeaderType (..)
, NoteTable
, NoteTable'
, Key (..)
, KeyTable
, SubstTable
, defaultParserState
, toKey
)
where
import Data.Default (Default (def))
import Data.Text (Text)
import Text.Parsec (SourcePos, getState, setState)
import Text.Pandoc.Builder (Blocks, HasMeta (..), Inlines)
import Text.Pandoc.Definition (Attr, Meta, Target, nullMeta)
import Text.Pandoc.Logging (LogMessage)
import Text.Pandoc.Options (ReaderOptions)
import Text.Pandoc.Parsing.Capabilities
import Text.Pandoc.Parsing.Future
import Text.Pandoc.TeX (Macro)
import qualified Data.Map as M
import qualified Data.Set as Set
import qualified Data.Text as T
data ParserState = ParserState
{ ParserState -> ReaderOptions
stateOptions :: ReaderOptions
, ParserState -> ParserContext
stateParserContext :: ParserContext
, ParserState -> QuoteContext
stateQuoteContext :: QuoteContext
, ParserState -> Bool
stateAllowLinks :: Bool
, ParserState -> Bool
stateAllowLineBreaks :: Bool
, ParserState -> Maybe SourcePos
stateLastStrPos :: Maybe SourcePos
, ParserState -> KeyTable
stateKeys :: KeyTable
, :: KeyTable
, ParserState -> SubstTable
stateSubstitutions :: SubstTable
, ParserState -> NoteTable
stateNotes :: NoteTable
, ParserState -> NoteTable'
stateNotes' :: NoteTable'
, ParserState -> Set Text
stateNoteRefs :: Set.Set Text
, ParserState -> Bool
stateInNote :: Bool
, ParserState -> Int
stateNoteNumber :: Int
, ParserState -> Meta
stateMeta :: Meta
, ParserState -> Future ParserState Meta
stateMeta' :: Future ParserState Meta
, ParserState -> Map Text Text
stateCitations :: M.Map Text Text
, :: [HeaderType]
, ParserState -> Set Text
stateIdentifiers :: Set.Set Text
, ParserState -> Int
stateNextExample :: Int
, ParserState -> Map Text Int
stateExamples :: M.Map Text Int
, ParserState -> Map Text Macro
stateMacros :: M.Map Text Macro
, ParserState -> Text
stateRstDefaultRole :: Text
, ParserState -> Maybe Text
stateRstHighlight :: Maybe Text
, ParserState -> Map Text (Text, Maybe Text, Attr)
stateRstCustomRoles :: M.Map Text (Text, Maybe Text, Attr)
, ParserState -> Maybe Inlines
stateCaption :: Maybe Inlines
, ParserState -> Maybe Text
stateInHtmlBlock :: Maybe Text
, ParserState -> Int
stateFencedDivLevel :: Int
, ParserState -> [Text]
stateContainers :: [Text]
, ParserState -> [LogMessage]
stateLogMessages :: [LogMessage]
, ParserState -> Bool
stateMarkdownAttribute :: Bool
}
instance Default ParserState where
def :: ParserState
def = ParserState
defaultParserState
instance HasMeta ParserState where
setMeta :: forall b. ToMetaValue b => Text -> b -> ParserState -> ParserState
setMeta Text
field b
val ParserState
st =
ParserState
st{ stateMeta :: Meta
stateMeta = Text -> b -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
setMeta Text
field b
val (Meta -> Meta) -> Meta -> Meta
forall a b. (a -> b) -> a -> b
$ ParserState -> Meta
stateMeta ParserState
st }
deleteMeta :: Text -> ParserState -> ParserState
deleteMeta Text
field ParserState
st =
ParserState
st{ stateMeta :: Meta
stateMeta = Text -> Meta -> Meta
forall a. HasMeta a => Text -> a -> a
deleteMeta Text
field (Meta -> Meta) -> Meta -> Meta
forall a b. (a -> b) -> a -> b
$ ParserState -> Meta
stateMeta ParserState
st }
instance HasReaderOptions ParserState where
extractReaderOptions :: ParserState -> ReaderOptions
extractReaderOptions = ParserState -> ReaderOptions
stateOptions
instance Monad m => HasQuoteContext ParserState m where
getQuoteContext :: forall s t. Stream s m t => ParsecT s ParserState m QuoteContext
getQuoteContext = ParserState -> QuoteContext
stateQuoteContext (ParserState -> QuoteContext)
-> ParsecT s ParserState m ParserState
-> ParsecT s ParserState m QuoteContext
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT s ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
withQuoteContext :: forall s a.
QuoteContext
-> ParsecT s ParserState m a -> ParsecT s ParserState m a
withQuoteContext QuoteContext
context ParsecT s ParserState m a
parser = do
ParserState
oldState <- ParsecT s ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let oldQuoteContext :: QuoteContext
oldQuoteContext = ParserState -> QuoteContext
stateQuoteContext ParserState
oldState
ParserState -> ParsecT s ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState ParserState
oldState { stateQuoteContext :: QuoteContext
stateQuoteContext = QuoteContext
context }
a
result <- ParsecT s ParserState m a
parser
ParserState
newState <- ParsecT s ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
ParserState -> ParsecT s ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState ParserState
newState { stateQuoteContext :: QuoteContext
stateQuoteContext = QuoteContext
oldQuoteContext }
a -> ParsecT s ParserState m a
forall a. a -> ParsecT s ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
result
instance HasIdentifierList ParserState where
extractIdentifierList :: ParserState -> Set Text
extractIdentifierList = ParserState -> Set Text
stateIdentifiers
updateIdentifierList :: (Set Text -> Set Text) -> ParserState -> ParserState
updateIdentifierList Set Text -> Set Text
f ParserState
st = ParserState
st{ stateIdentifiers :: Set Text
stateIdentifiers = Set Text -> Set Text
f (Set Text -> Set Text) -> Set Text -> Set Text
forall a b. (a -> b) -> a -> b
$ ParserState -> Set Text
stateIdentifiers ParserState
st }
instance HasMacros ParserState where
extractMacros :: ParserState -> Map Text Macro
extractMacros = ParserState -> Map Text Macro
stateMacros
updateMacros :: (Map Text Macro -> Map Text Macro) -> ParserState -> ParserState
updateMacros Map Text Macro -> Map Text Macro
f ParserState
st = ParserState
st{ stateMacros :: Map Text Macro
stateMacros = Map Text Macro -> Map Text Macro
f (Map Text Macro -> Map Text Macro)
-> Map Text Macro -> Map Text Macro
forall a b. (a -> b) -> a -> b
$ ParserState -> Map Text Macro
stateMacros ParserState
st }
instance HasLastStrPosition ParserState where
setLastStrPos :: Maybe SourcePos -> ParserState -> ParserState
setLastStrPos Maybe SourcePos
pos ParserState
st = ParserState
st{ stateLastStrPos :: Maybe SourcePos
stateLastStrPos = Maybe SourcePos
pos }
getLastStrPos :: ParserState -> Maybe SourcePos
getLastStrPos ParserState
st = ParserState -> Maybe SourcePos
stateLastStrPos ParserState
st
instance HasLogMessages ParserState where
addLogMessage :: LogMessage -> ParserState -> ParserState
addLogMessage LogMessage
msg ParserState
st = ParserState
st{ stateLogMessages :: [LogMessage]
stateLogMessages = LogMessage
msg LogMessage -> [LogMessage] -> [LogMessage]
forall a. a -> [a] -> [a]
: ParserState -> [LogMessage]
stateLogMessages ParserState
st }
getLogMessages :: ParserState -> [LogMessage]
getLogMessages ParserState
st = [LogMessage] -> [LogMessage]
forall a. [a] -> [a]
reverse ([LogMessage] -> [LogMessage]) -> [LogMessage] -> [LogMessage]
forall a b. (a -> b) -> a -> b
$ ParserState -> [LogMessage]
stateLogMessages ParserState
st
instance HasIncludeFiles ParserState where
getIncludeFiles :: ParserState -> [Text]
getIncludeFiles = ParserState -> [Text]
stateContainers
addIncludeFile :: Text -> ParserState -> ParserState
addIncludeFile Text
f ParserState
s = ParserState
s{ stateContainers :: [Text]
stateContainers = Text
f Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: ParserState -> [Text]
stateContainers ParserState
s }
dropLatestIncludeFile :: ParserState -> ParserState
dropLatestIncludeFile ParserState
s = ParserState
s { stateContainers :: [Text]
stateContainers = Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
drop Int
1 ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ ParserState -> [Text]
stateContainers ParserState
s }
data ParserContext
= ListItemState
| NullState
deriving (ParserContext -> ParserContext -> Bool
(ParserContext -> ParserContext -> Bool)
-> (ParserContext -> ParserContext -> Bool) -> Eq ParserContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParserContext -> ParserContext -> Bool
== :: ParserContext -> ParserContext -> Bool
$c/= :: ParserContext -> ParserContext -> Bool
/= :: ParserContext -> ParserContext -> Bool
Eq, Int -> ParserContext -> ShowS
[ParserContext] -> ShowS
ParserContext -> String
(Int -> ParserContext -> ShowS)
-> (ParserContext -> String)
-> ([ParserContext] -> ShowS)
-> Show ParserContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParserContext -> ShowS
showsPrec :: Int -> ParserContext -> ShowS
$cshow :: ParserContext -> String
show :: ParserContext -> String
$cshowList :: [ParserContext] -> ShowS
showList :: [ParserContext] -> ShowS
Show)
data
= Char
| Char
deriving (HeaderType -> HeaderType -> Bool
(HeaderType -> HeaderType -> Bool)
-> (HeaderType -> HeaderType -> Bool) -> Eq HeaderType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HeaderType -> HeaderType -> Bool
== :: HeaderType -> HeaderType -> Bool
$c/= :: HeaderType -> HeaderType -> Bool
/= :: HeaderType -> HeaderType -> Bool
Eq, Int -> HeaderType -> ShowS
[HeaderType] -> ShowS
HeaderType -> String
(Int -> HeaderType -> ShowS)
-> (HeaderType -> String)
-> ([HeaderType] -> ShowS)
-> Show HeaderType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HeaderType -> ShowS
showsPrec :: Int -> HeaderType -> ShowS
$cshow :: HeaderType -> String
show :: HeaderType -> String
$cshowList :: [HeaderType] -> ShowS
showList :: [HeaderType] -> ShowS
Show)
defaultParserState :: ParserState
defaultParserState :: ParserState
defaultParserState = ParserState
{ stateOptions :: ReaderOptions
stateOptions = ReaderOptions
forall a. Default a => a
def
, stateParserContext :: ParserContext
stateParserContext = ParserContext
NullState
, stateQuoteContext :: QuoteContext
stateQuoteContext = QuoteContext
NoQuote
, stateAllowLinks :: Bool
stateAllowLinks = Bool
True
, stateAllowLineBreaks :: Bool
stateAllowLineBreaks = Bool
True
, stateLastStrPos :: Maybe SourcePos
stateLastStrPos = Maybe SourcePos
forall a. Maybe a
Nothing
, stateKeys :: KeyTable
stateKeys = KeyTable
forall k a. Map k a
M.empty
, stateHeaderKeys :: KeyTable
stateHeaderKeys = KeyTable
forall k a. Map k a
M.empty
, stateSubstitutions :: SubstTable
stateSubstitutions = SubstTable
forall k a. Map k a
M.empty
, stateNotes :: NoteTable
stateNotes = []
, stateNotes' :: NoteTable'
stateNotes' = NoteTable'
forall k a. Map k a
M.empty
, stateNoteRefs :: Set Text
stateNoteRefs = Set Text
forall a. Set a
Set.empty
, stateInNote :: Bool
stateInNote = Bool
False
, stateNoteNumber :: Int
stateNoteNumber = Int
0
, stateMeta :: Meta
stateMeta = Meta
nullMeta
, stateMeta' :: Future ParserState Meta
stateMeta' = Meta -> Future ParserState Meta
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Meta
nullMeta
, stateCitations :: Map Text Text
stateCitations = Map Text Text
forall k a. Map k a
M.empty
, stateHeaderTable :: [HeaderType]
stateHeaderTable = []
, stateIdentifiers :: Set Text
stateIdentifiers = Set Text
forall a. Set a
Set.empty
, stateNextExample :: Int
stateNextExample = Int
1
, stateExamples :: Map Text Int
stateExamples = Map Text Int
forall k a. Map k a
M.empty
, stateMacros :: Map Text Macro
stateMacros = Map Text Macro
forall k a. Map k a
M.empty
, stateRstDefaultRole :: Text
stateRstDefaultRole = Text
"title-reference"
, stateRstHighlight :: Maybe Text
stateRstHighlight = Maybe Text
forall a. Maybe a
Nothing
, stateRstCustomRoles :: Map Text (Text, Maybe Text, Attr)
stateRstCustomRoles = Map Text (Text, Maybe Text, Attr)
forall k a. Map k a
M.empty
, stateCaption :: Maybe Inlines
stateCaption = Maybe Inlines
forall a. Maybe a
Nothing
, stateInHtmlBlock :: Maybe Text
stateInHtmlBlock = Maybe Text
forall a. Maybe a
Nothing
, stateFencedDivLevel :: Int
stateFencedDivLevel = Int
0
, stateContainers :: [Text]
stateContainers = []
, stateLogMessages :: [LogMessage]
stateLogMessages = []
, stateMarkdownAttribute :: Bool
stateMarkdownAttribute = Bool
False
}
type NoteTable = [(Text, Text)]
type NoteTable' = M.Map Text (SourcePos, Future ParserState Blocks)
newtype Key = Key Text deriving (Int -> Key -> ShowS
[Key] -> ShowS
Key -> String
(Int -> Key -> ShowS)
-> (Key -> String) -> ([Key] -> ShowS) -> Show Key
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Key -> ShowS
showsPrec :: Int -> Key -> ShowS
$cshow :: Key -> String
show :: Key -> String
$cshowList :: [Key] -> ShowS
showList :: [Key] -> ShowS
Show, ReadPrec [Key]
ReadPrec Key
Int -> ReadS Key
ReadS [Key]
(Int -> ReadS Key)
-> ReadS [Key] -> ReadPrec Key -> ReadPrec [Key] -> Read Key
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Key
readsPrec :: Int -> ReadS Key
$creadList :: ReadS [Key]
readList :: ReadS [Key]
$creadPrec :: ReadPrec Key
readPrec :: ReadPrec Key
$creadListPrec :: ReadPrec [Key]
readListPrec :: ReadPrec [Key]
Read, Key -> Key -> Bool
(Key -> Key -> Bool) -> (Key -> Key -> Bool) -> Eq Key
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
/= :: Key -> Key -> Bool
Eq, Eq Key
Eq Key
-> (Key -> Key -> Ordering)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Key)
-> (Key -> Key -> Key)
-> Ord Key
Key -> Key -> Bool
Key -> Key -> Ordering
Key -> Key -> Key
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Key -> Key -> Ordering
compare :: Key -> Key -> Ordering
$c< :: Key -> Key -> Bool
< :: Key -> Key -> Bool
$c<= :: Key -> Key -> Bool
<= :: Key -> Key -> Bool
$c> :: Key -> Key -> Bool
> :: Key -> Key -> Bool
$c>= :: Key -> Key -> Bool
>= :: Key -> Key -> Bool
$cmax :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
min :: Key -> Key -> Key
Ord)
toKey :: Text -> Key
toKey :: Text -> Key
toKey = Text -> Key
Key (Text -> Key) -> (Text -> Text) -> Text -> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unwords ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.words (Text -> [Text]) -> (Text -> Text) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
unbracket
where unbracket :: Text -> Text
unbracket Text
t
| Just (Char
'[', Text
t') <- Text -> Maybe (Char, Text)
T.uncons Text
t
, Just (Text
t'', Char
']') <- Text -> Maybe (Text, Char)
T.unsnoc Text
t'
= Text
t''
| Bool
otherwise
= Text
t
type KeyTable = M.Map Key (Target, Attr)
type SubstTable = M.Map Key Inlines