{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE LambdaCase            #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE ViewPatterns          #-}
module Text.Pandoc.Readers.HTML ( readHtml
                                , htmlTag
                                , htmlInBalanced
                                , isInlineTag
                                , isBlockTag
                                , isTextTag
                                , isCommentTag
                                , toAttr
                                ) where
import Control.Applicative ((<|>))
import Control.Monad (guard, mzero, unless, void)
import Control.Monad.Except (throwError, catchError)
import Control.Monad.Reader (ask, asks, lift, local, runReaderT)
import Data.ByteString.Base64 (encode)
import Data.Char (isAlphaNum, isLetter)
import Data.Default (Default (..), def)
import Data.Foldable (for_)
import Data.List.Split (splitWhen)
import Data.List (foldl')
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust, isNothing)
import Data.Either (partitionEithers)
import Data.Monoid (First (..))
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import Network.URI (nonStrictRelativeTo, parseURIReference)
import Text.HTML.TagSoup
import Text.HTML.TagSoup.Match
import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.CSS (pickStyleAttrProps)
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Definition
import Text.Pandoc.Readers.HTML.Parsing
import Text.Pandoc.Readers.HTML.Table (pTable)
import Text.Pandoc.Readers.HTML.TagCategories
import Text.Pandoc.Readers.HTML.Types
import Text.Pandoc.Readers.LaTeX (rawLaTeXInline)
import Text.Pandoc.Error
import Text.Pandoc.Logging
import Text.Pandoc.Options (
    Extension (Ext_epub_html_exts, Ext_empty_paragraphs, Ext_native_divs,
               Ext_native_spans, Ext_raw_html, Ext_line_blocks, Ext_raw_tex),
    ReaderOptions (readerExtensions, readerStripComments),
    extensionEnabled)
import Text.Pandoc.Parsing hiding ((<|>))
import Text.Pandoc.Shared (
    addMetaField, extractSpaces, htmlSpanLikeElements, renderTags',
    safeRead, tshow, formatCode)
import Text.Pandoc.URI (escapeURI)
import Text.Pandoc.Walk
import Text.TeXMath (readMathML, writeTeX)
import qualified Data.Sequence as Seq
readHtml :: (PandocMonad m, ToSources a)
         => ReaderOptions 
         -> a             
         -> m Pandoc
readHtml :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readHtml ReaderOptions
opts a
inp = do
  let tags :: [Tag Text]
tags = [Tag Text] -> [Tag Text]
stripPrefixes ([Tag Text] -> [Tag Text]) -> [Tag Text] -> [Tag Text]
forall a b. (a -> b) -> a -> b
$ [Tag Text] -> [Tag Text]
forall str. StringLike str => [Tag str] -> [Tag str]
canonicalizeTags ([Tag Text] -> [Tag Text]) -> [Tag Text] -> [Tag Text]
forall a b. (a -> b) -> a -> b
$
             ParseOptions Text -> Text -> [Tag Text]
forall str. StringLike str => ParseOptions str -> str -> [Tag str]
parseTagsOptions ParseOptions Text
forall str. StringLike str => ParseOptions str
parseOptions{ optTagPosition = True }
             (Sources -> Text
sourcesToText (Sources -> Text) -> Sources -> Text
forall a b. (a -> b) -> a -> b
$ a -> Sources
forall a. ToSources a => a -> Sources
toSources a
inp)
      parseDoc :: ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Pandoc
parseDoc = do
        Blocks
blocks <- Bool -> Blocks -> Blocks
fixPlains Bool
False (Blocks -> Blocks) -> ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Blocks]
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Blocks]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
        Meta
meta <- ParserState -> Meta
stateMeta (ParserState -> Meta)
-> (HTMLState -> ParserState) -> HTMLState -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HTMLState -> ParserState
parserState (HTMLState -> Meta)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Meta
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
        [Block]
bs' <- [Block] -> TagParser m [Block]
forall (m :: * -> *).
PandocMonad m =>
[Block] -> TagParser m [Block]
replaceNotes (Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
blocks)
        ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParsecT s st m ()
reportLogMessages
        Pandoc -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Pandoc
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Pandoc)
-> Pandoc
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc Meta
meta [Block]
bs'
      getError :: ParseError -> String
getError (ParseError -> [Message]
errorMessages -> [Message]
ms) = case [Message]
ms of
                                         []    -> String
""
                                         (Message
m:[Message]
_) -> Message -> String
messageString Message
m
  Either ParseError Pandoc
result <- (ReaderT HTMLLocal m (Either ParseError Pandoc)
 -> HTMLLocal -> m (Either ParseError Pandoc))
-> HTMLLocal
-> ReaderT HTMLLocal m (Either ParseError Pandoc)
-> m (Either ParseError Pandoc)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT HTMLLocal m (Either ParseError Pandoc)
-> HTMLLocal -> m (Either ParseError Pandoc)
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT HTMLLocal
forall a. Default a => a
def (ReaderT HTMLLocal m (Either ParseError Pandoc)
 -> m (Either ParseError Pandoc))
-> ReaderT HTMLLocal m (Either ParseError Pandoc)
-> m (Either ParseError Pandoc)
forall a b. (a -> b) -> a -> b
$
       ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Pandoc
-> HTMLState
-> String
-> [Tag Text]
-> ReaderT HTMLLocal m (Either ParseError Pandoc)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> String -> s -> m (Either ParseError a)
runParserT ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Pandoc
parseDoc
       (ParserState
-> [(Text, Blocks)]
-> Maybe URI
-> Set Text
-> [LogMessage]
-> Map Text Macro
-> ReaderOptions
-> Bool
-> HTMLState
HTMLState ParserState
forall a. Default a => a
def{ stateOptions = opts }
         [] Maybe URI
forall a. Maybe a
Nothing Set Text
forall a. Set a
Set.empty [] Map Text Macro
forall k a. Map k a
M.empty ReaderOptions
opts Bool
False)
       String
"source" [Tag Text]
tags
  case Either ParseError Pandoc
result of
    Right Pandoc
doc -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
doc
    Left  ParseError
err -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocParseError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ParseError -> String
getError ParseError
err
stripPrefixes :: [Tag Text] -> [Tag Text]
stripPrefixes :: [Tag Text] -> [Tag Text]
stripPrefixes = (Tag Text -> Tag Text) -> [Tag Text] -> [Tag Text]
forall a b. (a -> b) -> [a] -> [b]
map Tag Text -> Tag Text
stripPrefix
stripPrefix :: Tag Text -> Tag Text
stripPrefix :: Tag Text -> Tag Text
stripPrefix (TagOpen Text
s [Attribute Text]
as) = Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen ((Char -> Bool) -> Text -> Text
T.takeWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
':') Text
s) [Attribute Text]
as
stripPrefix (TagClose Text
s)   = Text -> Tag Text
forall str. str -> Tag str
TagClose ((Char -> Bool) -> Text -> Text
T.takeWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
':') Text
s)
stripPrefix Tag Text
x = Tag Text
x
replaceNotes :: PandocMonad m => [Block] -> TagParser m [Block]
replaceNotes :: forall (m :: * -> *).
PandocMonad m =>
[Block] -> TagParser m [Block]
replaceNotes [Block]
bs = do
  [(Text, Blocks)]
notes <- HTMLState -> [(Text, Blocks)]
noteTable (HTMLState -> [(Text, Blocks)])
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) [(Text, Blocks)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  (Inline
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inline)
-> [Block] -> TagParser m [Block]
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Inline -> m Inline) -> [Block] -> m [Block]
walkM ([(Text, Blocks)]
-> Inline
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inline
forall (m :: * -> *).
PandocMonad m =>
[(Text, Blocks)] -> Inline -> TagParser m Inline
replaceNotes' [(Text, Blocks)]
notes) [Block]
bs
replaceNotes' :: PandocMonad m
              => [(Text, Blocks)] -> Inline -> TagParser m Inline
replaceNotes' :: forall (m :: * -> *).
PandocMonad m =>
[(Text, Blocks)] -> Inline -> TagParser m Inline
replaceNotes' [(Text, Blocks)]
noteTbl (RawInline (Format Text
"noteref") Text
ref) =
  TagParser m Inline
-> (Blocks -> TagParser m Inline)
-> Maybe Blocks
-> TagParser m Inline
forall b a. b -> (a -> b) -> Maybe a -> b
maybe TagParser m Inline
warnNotFound (Inline -> TagParser m Inline
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inline -> TagParser m Inline)
-> (Blocks -> Inline) -> Blocks -> TagParser m Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Inline
Note ([Block] -> Inline) -> (Blocks -> [Block]) -> Blocks -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> [Block]
forall a. Many a -> [a]
B.toList) (Maybe Blocks -> TagParser m Inline)
-> Maybe Blocks -> TagParser m Inline
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Blocks)] -> Maybe Blocks
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
ref [(Text, Blocks)]
noteTbl
 where
  warnNotFound :: TagParser m Inline
warnNotFound = do
    SourcePos
pos <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
    LogMessage -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> LogMessage
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
ReferenceNotFound Text
ref SourcePos
pos
    Inline -> TagParser m Inline
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Block] -> Inline
Note [])
replaceNotes' [(Text, Blocks)]
_ Inline
x = Inline -> TagParser m Inline
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inline
x
setInChapter :: PandocMonad m => HTMLParser m s a -> HTMLParser m s a
setInChapter :: forall (m :: * -> *) s a.
PandocMonad m =>
HTMLParser m s a -> HTMLParser m s a
setInChapter = (HTMLLocal -> HTMLLocal)
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
forall a.
(HTMLLocal -> HTMLLocal)
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\HTMLLocal
s -> HTMLLocal
s {inChapter = True})
setInPlain :: PandocMonad m => HTMLParser m s a -> HTMLParser m s a
setInPlain :: forall (m :: * -> *) s a.
PandocMonad m =>
HTMLParser m s a -> HTMLParser m s a
setInPlain = (HTMLLocal -> HTMLLocal)
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
forall a.
(HTMLLocal -> HTMLLocal)
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\HTMLLocal
s -> HTMLLocal
s {inPlain = True})
setInListItem :: PandocMonad m => HTMLParser m s a -> HTMLParser m s a
setInListItem :: forall (m :: * -> *) s a.
PandocMonad m =>
HTMLParser m s a -> HTMLParser m s a
setInListItem = (HTMLLocal -> HTMLLocal)
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
forall a.
(HTMLLocal -> HTMLLocal)
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local (\HTMLLocal
s -> HTMLLocal
s {inListItem = True})
pHtml :: PandocMonad m => TagParser m Blocks
pHtml :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHtml = do
  (TagOpen Text
"html" [Attribute Text]
attr) <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny
  Maybe Text
-> (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"lang" [Attribute Text]
attr Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"xml:lang" [Attribute Text]
attr) ((Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$
    (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((HTMLState -> HTMLState)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> (Text -> HTMLState -> HTMLState)
-> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines -> HTMLState -> HTMLState
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> HTMLState -> HTMLState
B.setMeta Text
"lang" (Inlines -> HTMLState -> HTMLState)
-> (Text -> Inlines) -> Text -> HTMLState -> HTMLState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.text
  Text -> TagParser m Blocks -> TagParser m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"html" TagParser m Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
pBody :: PandocMonad m => TagParser m Blocks
pBody :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pBody = do
  (TagOpen Text
"body" [Attribute Text]
attr) <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny
  Maybe Text
-> (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"lang" [Attribute Text]
attr Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"xml:lang" [Attribute Text]
attr) ((Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$
    (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((HTMLState -> HTMLState)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> (Text -> HTMLState -> HTMLState)
-> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines -> HTMLState -> HTMLState
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> HTMLState -> HTMLState
B.setMeta Text
"lang" (Inlines -> HTMLState -> HTMLState)
-> (Text -> Inlines) -> Text -> HTMLState -> HTMLState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.text
  Text -> TagParser m Blocks -> TagParser m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"body" TagParser m Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
pHead :: PandocMonad m => TagParser m Blocks
pHead :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHead = Text -> TagParser m Blocks -> TagParser m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"head" (TagParser m Blocks -> TagParser m Blocks)
-> TagParser m Blocks -> TagParser m Blocks
forall a b. (a -> b) -> a -> b
$ TagParser m Blocks
pTitle TagParser m Blocks -> TagParser m Blocks -> TagParser m Blocks
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TagParser m Blocks
pMetaTag TagParser m Blocks -> TagParser m Blocks -> TagParser m Blocks
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TagParser m Blocks
pBaseTag TagParser m Blocks -> TagParser m Blocks -> TagParser m Blocks
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> TagParser m Blocks
forall a b.
a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny)
  where pTitle :: TagParser m Blocks
pTitle = Text -> TagParser m Inlines -> TagParser m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"title" TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline TagParser m Inlines
-> (Inlines -> TagParser m Blocks) -> TagParser m Blocks
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> (a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Inlines -> TagParser m Blocks
forall {a} {m :: * -> *} {u} {b} {s}.
(Monoid a, Monad m, HasMeta u, ToMetaValue b) =>
b -> ParsecT s u m a
setTitle (Inlines -> TagParser m Blocks)
-> (Inlines -> Inlines) -> Inlines -> TagParser m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
trimInlines
        setTitle :: b -> ParsecT s u m a
setTitle b
t = a
forall a. Monoid a => a
mempty a -> ParsecT s u m () -> ParsecT s u m a
forall a b. a -> ParsecT s u m b -> ParsecT s u m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (u -> u) -> ParsecT s u m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (Text -> b -> u -> u
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> u -> u
B.setMeta Text
"title" b
t)
        pMetaTag :: TagParser m Blocks
pMetaTag = do
          Tag Text
mt <- (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"meta" [])
          let name :: Text
name = Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"name" Tag Text
mt
          if Text -> Bool
T.null Text
name
             then Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
             else do
               let content :: Text
content = Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"content" Tag Text
mt
               (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((HTMLState -> HTMLState)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ \HTMLState
s ->
                 let ps :: ParserState
ps = HTMLState -> ParserState
parserState HTMLState
s in
                 HTMLState
s{ parserState = ps{
                      stateMeta = addMetaField name (B.text content)
                                   (stateMeta ps) } }
               Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
        pBaseTag :: TagParser m Blocks
pBaseTag = do
          Tag Text
bt <- (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"base" [])
          (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((HTMLState -> HTMLState)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ \HTMLState
st -> HTMLState
st{ baseHref =
               parseURIReference $ T.unpack $ fromAttrib "href" bt }
          Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
block :: PandocMonad m => TagParser m Blocks
block :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block = ((do
  Tag Text
tag <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ((Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy Tag Text -> Bool
isBlockTag)
  Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
forall s (m :: * -> *) t b.
Stream s m t =>
(ReaderOptions -> b) -> ParsecT s HTMLState m b
getOption ReaderOptions -> Extensions
readerExtensions
  case Tag Text
tag of
    TagOpen Text
name [Attribute Text]
attr ->
      let type' :: Text
type' = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$
                     Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attr Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"epub:type" [Attribute Text]
attr
          epubExts :: Bool
epubExts = Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_epub_html_exts Extensions
exts
      in
      case Text
name of
        Text
_ | Text
name Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
sectioningContent
          , Bool
epubExts
          , Text
"chapter" Text -> Text -> Bool
`T.isInfixOf` Text
type'
          -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
eSection
        Text
_ | Bool
epubExts
          , Text
type' Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"footnotes", Text
"rearnotes"]
          -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
eFootnotes
        Text
_ | Bool
epubExts
          , Text
type' Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"footnote", Text
"rearnote"]
          -> Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b.
a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
eFootnote
        Text
_ | Bool
epubExts
          , Text
type' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"toc"
          -> Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b.
a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
eTOC
        Text
_ | Text
"titlepage" Text -> Text -> Bool
`T.isInfixOf` Text
type'
          , Text
name Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Text
"section" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
groupingContent)
          -> Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b.
a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
eTitlePage
        Text
"p" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pPara
        Text
"h1" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHeader
        Text
"h2" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHeader
        Text
"h3" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHeader
        Text
"h4" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHeader
        Text
"h5" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHeader
        Text
"h6" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHeader
        Text
"blockquote" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pBlockQuote
        Text
"pre" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pCodeBlock
        Text
"ul" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pBulletList
        Text
"ol" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pOrderedList
        Text
"dl" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pDefinitionList
        Text
"table" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *).
PandocMonad m =>
TagParser m Blocks -> TagParser m Blocks
pTable ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
        Text
"hr" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHrule
        Text
"html" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHtml
        Text
"head" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHead
        Text
"body" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pBody
        Text
"div"
          | Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_line_blocks Extensions
exts
          , Just Text
"line-block" <- Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Attribute Text]
attr
          -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pLineBlock
          | Bool
otherwise
          -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pDiv
        Text
"section" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pDiv
        Text
"header" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pDiv
        Text
"main" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pDiv
        Text
"figure" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pFigure
        Text
"iframe" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pIframe
        Text
"style" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pRawHtmlBlock
        Text
"textarea" -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pRawHtmlBlock
        Text
"switch"
          | Bool
epubExts
          -> (Inlines -> Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
(Inlines -> a) -> TagParser m a -> TagParser m a
eSwitch Inlines -> Blocks
B.para ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
        Text
_ -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
    Tag Text
_ -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero) ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pPlain ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pRawHtmlBlock) ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> (Blocks
    -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> (a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Blocks
res ->
        Blocks
res Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b.
a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> m ()
trace (Int -> Text -> Text
T.take Int
60 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Block] -> Text
forall a. Show a => a -> Text
tshow ([Block] -> Text) -> [Block] -> Text
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
res)
namespaces :: PandocMonad m => [(Text, TagParser m Inlines)]
namespaces :: forall (m :: * -> *).
PandocMonad m =>
[(Text, TagParser m Inlines)]
namespaces = [(Text
mathMLNamespace, Bool -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => Bool -> TagParser m Inlines
pMath Bool
True)]
mathMLNamespace :: Text
mathMLNamespace :: Text
mathMLNamespace = Text
"http://www.w3.org/1998/Math/MathML"
eSwitch :: (PandocMonad m, Monoid a)
        => (Inlines -> a)
        -> TagParser m a
        -> TagParser m a
eSwitch :: forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
(Inlines -> a) -> TagParser m a -> TagParser m a
eSwitch Inlines -> a
constructor TagParser m a
parser = TagParser m a -> TagParser m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TagParser m a -> TagParser m a) -> TagParser m a -> TagParser m a
forall a b. (a -> b) -> a -> b
$ do
  Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_epub_html_exts
  (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"switch" [])
  Maybe Inlines
cases <- First Inlines -> Maybe Inlines
forall a. First a -> Maybe a
getFirst (First Inlines -> Maybe Inlines)
-> ([First Inlines] -> First Inlines)
-> [First Inlines]
-> Maybe Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [First Inlines] -> First Inlines
forall a. Monoid a => [a] -> a
mconcat ([First Inlines] -> Maybe Inlines)
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) [First Inlines]
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Maybe Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
            ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (First Inlines)
-> TagParser m (Tag Text)
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) [First Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (Maybe Inlines -> First Inlines
forall a. Maybe a -> First a
First (Maybe Inlines -> First Inlines)
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Maybe Inlines)
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (First Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Maybe Inlines)
forall (m :: * -> *). PandocMonad m => TagParser m (Maybe Inlines)
eCase ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Maybe Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Maybe Inlines)
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank) )
              (TagParser m (Tag Text) -> TagParser m (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (TagParser m (Tag Text) -> TagParser m (Tag Text))
-> TagParser m (Tag Text) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ TagParser m (Tag Text) -> TagParser m (Tag Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TagParser m (Tag Text) -> TagParser m (Tag Text))
-> TagParser m (Tag Text) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"default" []))
  ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank
  a
fallback <- Text -> TagParser m a -> TagParser m a
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"default" (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> TagParser m a -> TagParser m a
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TagParser m a
parser TagParser m a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> TagParser m a
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank)
  ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank
  (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> Tag Text -> Bool
matchTagClose Text
"switch")
  a -> TagParser m a
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> TagParser m a) -> a -> TagParser m a
forall a b. (a -> b) -> a -> b
$ a -> (Inlines -> a) -> Maybe Inlines -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
fallback Inlines -> a
constructor Maybe Inlines
cases
eCase :: PandocMonad m => TagParser m (Maybe Inlines)
eCase :: forall (m :: * -> *). PandocMonad m => TagParser m (Maybe Inlines)
eCase = do
  ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank
  TagOpen Text
_ [Attribute Text]
attr' <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"case" [])
  let attr :: [Attribute Text]
attr = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attr'
  case (Text
 -> [(Text, TagParser m Inlines)] -> Maybe (TagParser m Inlines))
-> [(Text, TagParser m Inlines)]
-> Text
-> Maybe (TagParser m Inlines)
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text
-> [(Text, TagParser m Inlines)] -> Maybe (TagParser m Inlines)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [(Text, TagParser m Inlines)]
forall (m :: * -> *).
PandocMonad m =>
[(Text, TagParser m Inlines)]
namespaces (Text -> Maybe (TagParser m Inlines))
-> Maybe Text -> Maybe (TagParser m Inlines)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"required-namespace" [Attribute Text]
attr of
    Just TagParser m Inlines
p -> Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just (Inlines -> Maybe Inlines)
-> TagParser m Inlines -> TagParser m (Maybe Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> TagParser m Inlines -> TagParser m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"case" (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> TagParser m Inlines -> TagParser m Inlines
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> TagParser m Inlines
p TagParser m Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> TagParser m Inlines
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank)
    Maybe (TagParser m Inlines)
Nothing -> Maybe Inlines
forall a. Maybe a
Nothing Maybe Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
-> TagParser m (Maybe Inlines)
forall a b.
a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny ((Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> Tag Text -> Bool
matchTagClose Text
"case"))
eFootnote :: PandocMonad m => TagParser m ()
 = do
  Extension -> TagParser m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_epub_html_exts
  TagOpen Text
tag [Attribute Text]
attr' <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy
    (\case
       TagOpen Text
_ [Attribute Text]
attr'
         -> case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attr' Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"epub:type" [Attribute Text]
attr' of
              Just Text
"footnote" -> Bool
True
              Just Text
"rearnote" -> Bool
True
              Maybe Text
_ -> Bool
False
       Tag Text
_ -> Bool
False)
  let attr :: [Attribute Text]
attr = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attr'
  let ident :: Text
ident = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [Attribute Text]
attr)
  Blocks
content <- Text -> TagParser m Blocks -> TagParser m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
tag TagParser m Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
  (HTMLState -> HTMLState) -> TagParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((HTMLState -> HTMLState) -> TagParser m ())
-> (HTMLState -> HTMLState) -> TagParser m ()
forall a b. (a -> b) -> a -> b
$ \HTMLState
s ->
    HTMLState
s {noteTable = (ident, content) : noteTable s}
eFootnotes :: PandocMonad m => TagParser m Blocks
 = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  let notes :: [Text]
notes = [Text
"footnotes", Text
"rearnotes"]
  Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_epub_html_exts
  (TagOpen Text
tag [Attribute Text]
attr') <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny
  let attr :: [Attribute Text]
attr = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attr'
  Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
notes)
          (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attr Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"epub:type" [Attribute Text]
attr)
  (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((HTMLState -> HTMLState)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ \HTMLState
s -> HTMLState
s{ inFootnotes = True }
  Blocks
result <- Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
tag ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
  (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((HTMLState -> HTMLState)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> (HTMLState -> HTMLState)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ \HTMLState
s -> HTMLState
s{ inFootnotes = False }
  if Blocks -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Blocks
result
     
     then Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
result
     
     
     else Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith ([Attribute Text] -> Attr
toAttr [Attribute Text]
attr') Blocks
result
eNoteref :: PandocMonad m => TagParser m Inlines
eNoteref :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
eNoteref = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ do
  Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_epub_html_exts
  TagOpen Text
tag [Attribute Text]
attr <-
    (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (\case
                 TagOpen Text
_ [Attribute Text]
as
                    -> (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
as Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"epub:type" [Attribute Text]
as)
                        Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"noteref"
                 Tag Text
_  -> Bool
False)
  Text
ident <- case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"href" [Attribute Text]
attr Maybe Text -> (Text -> Maybe (Char, Text)) -> Maybe (Char, Text)
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe (Char, Text)
T.uncons of
             Just (Char
'#', Text
rest) -> Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
rest
             Maybe (Char, Text)
_ -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
forall a. ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  [Tag Text]
_ <- TagParser m (Tag Text)
-> TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill TagParser m (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny ((Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (\case
                                   TagClose Text
t -> Text
t Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
tag
                                   Tag Text
_          -> Bool
False))
  Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines
B.rawInline Text
"noteref" Text
ident
eTOC :: PandocMonad m => TagParser m ()
eTOC :: forall (m :: * -> *). PandocMonad m => TagParser m ()
eTOC = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ do
  Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_epub_html_exts
  (TagOpen Text
tag [Attribute Text]
attr) <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny
  Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attr Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"epub:type" [Attribute Text]
attr) Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"toc"
  ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
tag ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block)
pBulletList :: PandocMonad m => TagParser m Blocks
pBulletList :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pBulletList = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"ul" [])
  let nonItem :: TagParser m (Tag Text)
nonItem = (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (\Tag Text
t ->
                  Bool -> Bool
not ((Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"li",Text
"ol",Text
"ul",Text
"dl"]) (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True) Tag Text
t) Bool -> Bool -> Bool
&&
                  Bool -> Bool
not (Text -> Tag Text -> Bool
matchTagClose Text
"ul" Tag Text
t))
  
  
  TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TagParser m (Tag Text)
nonItem
  [Blocks]
items <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Blocks]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
PandocMonad m =>
TagParser m a -> TagParser m Blocks
pListItem TagParser m (Tag Text)
nonItem) (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"ul")
  Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
B.bulletList ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall a b. (a -> b) -> a -> b
$ (Blocks -> Blocks) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Blocks -> Blocks
fixPlains Bool
True) [Blocks]
items
pListItem :: PandocMonad m => TagParser m a -> TagParser m Blocks
pListItem :: forall (m :: * -> *) a.
PandocMonad m =>
TagParser m a -> TagParser m Blocks
pListItem TagParser m a
nonItem = HTMLParser m [Tag Text] Blocks -> HTMLParser m [Tag Text] Blocks
forall (m :: * -> *) s a.
PandocMonad m =>
HTMLParser m s a -> HTMLParser m s a
setInListItem (HTMLParser m [Tag Text] Blocks -> HTMLParser m [Tag Text] Blocks)
-> HTMLParser m [Tag Text] Blocks -> HTMLParser m [Tag Text] Blocks
forall a b. (a -> b) -> a -> b
$ do
  TagOpen Text
_ [Attribute Text]
attr' <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"li" [])
  let attr :: [Attribute Text]
attr = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attr'
  let addId :: Text -> Blocks -> Blocks
addId Text
ident Blocks
bs = case Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
bs of
                           (Plain [Inline]
ils:[Block]
xs) -> [Block] -> Blocks
forall a. [a] -> Many a
B.fromList ([Inline] -> Block
Plain
                                [Attr -> [Inline] -> Inline
Span (Text
ident, [], []) [Inline]
ils] Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block]
xs)
                           [Block]
_ -> Attr -> Blocks -> Blocks
B.divWith (Text
ident, [], []) Blocks
bs
  Blocks
item <- Text
-> HTMLParser m [Tag Text] Blocks -> HTMLParser m [Tag Text] Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"li" HTMLParser m [Tag Text] Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
  TagParser m a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TagParser m a
nonItem
  [Blocks]
orphans <- HTMLParser m [Tag Text] Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (do ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ((Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"li" []))
                      ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ((Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy Tag Text -> Bool
forall str. Tag str -> Bool
isTagClose)
                      HTMLParser m [Tag Text] Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block) 
  Blocks -> HTMLParser m [Tag Text] Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> HTMLParser m [Tag Text] Blocks)
-> Blocks -> HTMLParser m [Tag Text] Blocks
forall a b. (a -> b) -> a -> b
$ (Blocks -> Blocks)
-> (Text -> Blocks -> Blocks) -> Maybe Text -> Blocks -> Blocks
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Blocks -> Blocks
forall a. a -> a
id Text -> Blocks -> Blocks
addId (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [Attribute Text]
attr) (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ Blocks
item Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
orphans
pCheckbox :: PandocMonad m => TagParser m Inlines
pCheckbox :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pCheckbox = do
  TagOpen Text
_ [Attribute Text]
attr' <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"input" [(Text
"type",Text
"checkbox")]
  TagClose Text
_ <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> Tag Text -> Bool
matchTagClose Text
"input")
  let attr :: [Attribute Text]
attr = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attr'
  let isChecked :: Bool
isChecked = Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Text -> Bool) -> Maybe Text -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"checked" [Attribute Text]
attr
  let escapeSequence :: Inlines
escapeSequence = Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ if Bool
isChecked then Text
"\9746" else Text
"\9744"
  Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TagParser m Inlines) -> Inlines -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
escapeSequence Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.space
parseListStyleType :: Text -> ListNumberStyle
parseListStyleType :: Text -> ListNumberStyle
parseListStyleType Text
"lower-roman" = ListNumberStyle
LowerRoman
parseListStyleType Text
"upper-roman" = ListNumberStyle
UpperRoman
parseListStyleType Text
"lower-alpha" = ListNumberStyle
LowerAlpha
parseListStyleType Text
"upper-alpha" = ListNumberStyle
UpperAlpha
parseListStyleType Text
"decimal"     = ListNumberStyle
Decimal
parseListStyleType Text
_             = ListNumberStyle
DefaultStyle
parseTypeAttr :: Text -> ListNumberStyle
parseTypeAttr :: Text -> ListNumberStyle
parseTypeAttr Text
"i" = ListNumberStyle
LowerRoman
parseTypeAttr Text
"I" = ListNumberStyle
UpperRoman
parseTypeAttr Text
"a" = ListNumberStyle
LowerAlpha
parseTypeAttr Text
"A" = ListNumberStyle
UpperAlpha
parseTypeAttr Text
"1" = ListNumberStyle
Decimal
parseTypeAttr Text
_   = ListNumberStyle
DefaultStyle
pOrderedList :: PandocMonad m => TagParser m Blocks
pOrderedList :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pOrderedList = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  TagOpen Text
_ [Attribute Text]
attribs' <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"ol" [])
  Bool
isNoteList <- HTMLState -> Bool
inFootnotes (HTMLState -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  let attribs :: [Attribute Text]
attribs = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attribs'
  let start :: Int
start = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"start" [Attribute Text]
attribs Maybe Text -> (Text -> Maybe Int) -> Maybe Int
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead
  let style :: ListNumberStyle
style = ListNumberStyle -> Maybe ListNumberStyle -> ListNumberStyle
forall a. a -> Maybe a -> a
fromMaybe ListNumberStyle
DefaultStyle
         (Maybe ListNumberStyle -> ListNumberStyle)
-> Maybe ListNumberStyle -> ListNumberStyle
forall a b. (a -> b) -> a -> b
$  (Text -> ListNumberStyle
parseTypeAttr      (Text -> ListNumberStyle) -> Maybe Text -> Maybe ListNumberStyle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attribs)
        Maybe ListNumberStyle
-> Maybe ListNumberStyle -> Maybe ListNumberStyle
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Text -> ListNumberStyle
parseListStyleType (Text -> ListNumberStyle) -> Maybe Text -> Maybe ListNumberStyle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Attribute Text]
attribs)
        Maybe ListNumberStyle
-> Maybe ListNumberStyle -> Maybe ListNumberStyle
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Text -> ListNumberStyle
parseListStyleType (Text -> ListNumberStyle) -> Maybe Text -> Maybe ListNumberStyle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"style" [Attribute Text]
attribs Maybe Text -> (Text -> Maybe Text) -> Maybe Text
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Text
pickListStyle))
        where
          pickListStyle :: Text -> Maybe Text
pickListStyle = [Text] -> Text -> Maybe Text
pickStyleAttrProps [Text
"list-style-type", Text
"list-style"]
  let nonItem :: TagParser m (Tag Text)
nonItem = (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (\Tag Text
t ->
                  Bool -> Bool
not ((Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"li",Text
"ol",Text
"ul",Text
"dl"]) (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True) Tag Text
t) Bool -> Bool -> Bool
&&
                  Bool -> Bool
not (Text -> Tag Text -> Bool
matchTagClose Text
"ol" Tag Text
t))
  
  
  TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TagParser m (Tag Text)
nonItem
  if Bool
isNoteList
     then do
       [()]
_ <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [()]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
eFootnote ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => TagParser m ()
pBlank) (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"ol")
       Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
     else do
       [Blocks]
items <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Blocks]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
PandocMonad m =>
TagParser m a -> TagParser m Blocks
pListItem TagParser m (Tag Text)
nonItem) (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"ol")
       Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ ListAttributes -> [Blocks] -> Blocks
B.orderedListWith (Int
start, ListNumberStyle
style, ListNumberDelim
DefaultDelim) ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall a b. (a -> b) -> a -> b
$
                (Blocks -> Blocks) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Blocks -> Blocks
fixPlains Bool
True) [Blocks]
items
pDefinitionList :: PandocMonad m => TagParser m Blocks
pDefinitionList :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pDefinitionList = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"dl" [])
  [(Inlines, [Blocks])]
items <- ParsecT
  [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks])
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) [(Inlines, [Blocks])]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT
  [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks])
forall (m :: * -> *).
PandocMonad m =>
TagParser m (Inlines, [Blocks])
pDefListItem (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"dl")
  Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ [(Inlines, [Blocks])] -> Blocks
B.definitionList [(Inlines, [Blocks])]
items
pDefListItem :: PandocMonad m => TagParser m (Inlines, [Blocks])
pDefListItem :: forall (m :: * -> *).
PandocMonad m =>
TagParser m (Inlines, [Blocks])
pDefListItem = ParsecT
  [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks])
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
   [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks])
 -> ParsecT
      [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks]))
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks])
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks])
forall a b. (a -> b) -> a -> b
$ do
  let nonItem :: TagParser m (Tag Text)
nonItem = (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (\Tag Text
t -> Bool -> Bool
not (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"dt" [] Tag Text
t) Bool -> Bool -> Bool
&&
                  Bool -> Bool
not (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"dd" [] Tag Text
t) Bool -> Bool -> Bool
&& Bool -> Bool
not (Text -> Tag Text -> Bool
matchTagClose Text
"dl" Tag Text
t))
  [Inlines]
terms <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TagParser m (Tag Text)
nonItem ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"dt" ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline)
  [Blocks]
defs  <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TagParser m (Tag Text)
nonItem ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"dd" ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block)
  TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany TagParser m (Tag Text)
nonItem
  let term :: Inlines
term = (Inlines -> Inlines -> Inlines) -> Inlines -> [Inlines] -> Inlines
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Inlines
x Inlines
y -> if Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
x
                                then Inlines -> Inlines
trimInlines Inlines
y
                                else Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
B.linebreak Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
trimInlines Inlines
y)
                    Inlines
forall a. Monoid a => a
mempty [Inlines]
terms
  (Inlines, [Blocks])
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Inlines, [Blocks])
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
term, (Blocks -> Blocks) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Blocks -> Blocks
fixPlains Bool
True) [Blocks]
defs)
fixPlains :: Bool -> Blocks -> Blocks
fixPlains :: Bool -> Blocks -> Blocks
fixPlains Bool
inList Blocks
bs = if (Block -> Bool) -> [Block] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Block -> Bool
isParaish [Block]
bs'
                         then [Block] -> Blocks
forall a. [a] -> Many a
B.fromList ([Block] -> Blocks) -> [Block] -> Blocks
forall a b. (a -> b) -> a -> b
$ (Block -> Block) -> [Block] -> [Block]
forall a b. (a -> b) -> [a] -> [b]
map Block -> Block
plainToPara [Block]
bs'
                         else Blocks
bs
  where isParaish :: Block -> Bool
isParaish Para{}           = Bool
True
        isParaish CodeBlock{}      = Bool
True
        isParaish Header{}         = Bool
True
        isParaish BlockQuote{}     = Bool
True
        isParaish BulletList{}     = Bool -> Bool
not Bool
inList
        isParaish OrderedList{}    = Bool -> Bool
not Bool
inList
        isParaish DefinitionList{} = Bool -> Bool
not Bool
inList
        isParaish Block
_                = Bool
False
        plainToPara :: Block -> Block
plainToPara (Plain [Inline]
xs) = [Inline] -> Block
Para [Inline]
xs
        plainToPara Block
x          = Block
x
        bs' :: [Block]
bs' = Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
bs
pRawTag :: PandocMonad m => TagParser m Text
pRawTag :: forall (m :: * -> *). PandocMonad m => TagParser m Text
pRawTag = do
  Tag Text
tag <- TagParser m (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny
  let ignorable :: a -> Bool
ignorable a
x = a
x a -> [a] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a
"html",a
"head",a
"body",a
"!DOCTYPE",a
"?xml"]
  if (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen Text -> Bool
forall {a}. (Eq a, IsString a) => a -> Bool
ignorable (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True) Tag Text
tag Bool -> Bool -> Bool
|| (Text -> Bool) -> Tag Text -> Bool
forall str. (str -> Bool) -> Tag str -> Bool
tagClose Text -> Bool
forall {a}. (Eq a, IsString a) => a -> Bool
ignorable Tag Text
tag
     then Text -> TagParser m Text
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
forall a. Monoid a => a
mempty
     else Text -> TagParser m Text
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> TagParser m Text) -> Text -> TagParser m Text
forall a b. (a -> b) -> a -> b
$ [Tag Text] -> Text
renderTags' [Tag Text
tag]
pLineBlock :: PandocMonad m => TagParser m Blocks
pLineBlock :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pLineBlock = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_line_blocks
  Tag Text
_ <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"div") ([Attribute Text] -> [Attribute Text] -> Bool
forall a. Eq a => a -> a -> Bool
== [(Text
"class",Text
"line-block")])
  Inlines
ils <- Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline ((Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Text -> Bool) -> Tag Text -> Bool
forall str. (str -> Bool) -> Tag str -> Bool
tagClose (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"div")))
  let lns :: [Inlines]
lns = ([Inline] -> Inlines) -> [[Inline]] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map [Inline] -> Inlines
forall a. [a] -> Many a
B.fromList ([[Inline]] -> [Inlines]) -> [[Inline]] -> [Inlines]
forall a b. (a -> b) -> a -> b
$
            (Inline -> Bool) -> [Inline] -> [[Inline]]
forall a. (a -> Bool) -> [a] -> [[a]]
splitWhen (Inline -> Inline -> Bool
forall a. Eq a => a -> a -> Bool
== Inline
LineBreak) ([Inline] -> [[Inline]]) -> [Inline] -> [[Inline]]
forall a b. (a -> b) -> a -> b
$ (Inline -> Bool) -> [Inline] -> [Inline]
forall a. (a -> Bool) -> [a] -> [a]
filter (Inline -> Inline -> Bool
forall a. Eq a => a -> a -> Bool
/= Inline
SoftBreak) ([Inline] -> [Inline]) -> [Inline] -> [Inline]
forall a b. (a -> b) -> a -> b
$
            Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
ils
  Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Blocks
B.lineBlock [Inlines]
lns
isDivLike :: Text -> Bool
isDivLike :: Text -> Bool
isDivLike Text
"div"     = Bool
True
isDivLike Text
"section" = Bool
True
isDivLike Text
"header"  = Bool
True
isDivLike Text
"main"    = Bool
True
isDivLike Text
_         = Bool
False
pDiv :: PandocMonad m => TagParser m Blocks
pDiv :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pDiv = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_native_divs
  TagOpen Text
tag [Attribute Text]
attr' <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen Text -> Bool
isDivLike (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  let (Text
ident, [Text]
classes, [Attribute Text]
kvs) = [Attribute Text] -> Attr
toAttr [Attribute Text]
attr'
  Blocks
contents <- Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
tag ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
  let contents' :: Blocks
contents' = case Blocks -> Seq Block
forall a. Many a -> Seq a
B.unMany Blocks
contents of
                    Header Int
lev (Text
hident,[Text]
hclasses,[Attribute Text]
hkvs) [Inline]
ils Seq.:<| Seq Block
rest
                        | Text
hident Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
ident ->
                          Seq Block -> Blocks
forall a. Seq a -> Many a
B.Many (Seq Block -> Blocks) -> Seq Block -> Blocks
forall a b. (a -> b) -> a -> b
$ Int -> Attr -> [Inline] -> Block
Header Int
lev (Text
"",[Text]
hclasses,[Attribute Text]
hkvs) [Inline]
ils Block -> Seq Block -> Seq Block
forall a. a -> Seq a -> Seq a
Seq.<| Seq Block
rest
                    Seq Block
_ -> Blocks
contents
  let classes' :: [Text]
classes' = if Text
tag Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"section"
                    then Text
"section"Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
classes
                    else [Text]
classes
      kvs' :: [Attribute Text]
kvs' = if Text
tag Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"main" Bool -> Bool -> Bool
&& Maybe Text -> Bool
forall a. Maybe a -> Bool
isNothing (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"role" [Attribute Text]
kvs)
               then (Text
"role", Text
"main")Attribute Text -> [Attribute Text] -> [Attribute Text]
forall a. a -> [a] -> [a]
:[Attribute Text]
kvs
               else [Attribute Text]
kvs
  Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith (Text
ident, [Text]
classes', [Attribute Text]
kvs') Blocks
contents'
pIframe :: PandocMonad m => TagParser m Blocks
pIframe :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pIframe = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_raw_html
  Tag Text
tag <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"iframe") (Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Text -> Bool)
-> ([Attribute Text] -> Maybe Text) -> [Attribute Text] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"src"))
  Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"iframe" ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
  Text
url <- Text -> TagParser m Text
forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
canonicalizeUrl (Text -> TagParser m Text) -> Text -> TagParser m Text
forall a b. (a -> b) -> a -> b
$ Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"src" Tag Text
tag
  if Text -> Bool
T.null Text
url
     then Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Text -> TagParser m a
ignore (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ [Tag Text] -> Text
renderTags' [Tag Text
tag, Text -> Tag Text
forall str. str -> Tag str
TagClose Text
"iframe"]
     else ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> (PandocError
    -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> (PandocError
    -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall e (m :: * -> *) a.
MonadError e m =>
m a -> (e -> m a) -> m a
catchError
       (do (ByteString
bs, Maybe Text
mbMime) <- Text
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (ByteString, Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> m (ByteString, Maybe Text)
openURL Text
url
           case Maybe Text
mbMime of
             Just Text
mt
               | Text
"text/html" Text -> Text -> Bool
`T.isPrefixOf` Text
mt -> do
                    let inp :: Text
inp = ByteString -> Text
UTF8.toText ByteString
bs
                    ReaderOptions
opts <- HTMLState -> ReaderOptions
readerOpts (HTMLState -> ReaderOptions)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ReaderOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
                    Pandoc Meta
_ [Block]
contents <- ReaderOptions
-> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Pandoc
forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readHtml ReaderOptions
opts Text
inp
                    Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith (Text
"",[Text
"iframe"],[]) (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ [Block] -> Blocks
forall a. [a] -> Many a
B.fromList [Block]
contents
               | Text
"image/" Text -> Text -> Bool
`T.isPrefixOf` Text
mt -> do
                    Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith (Text
"",[Text
"iframe"],[]) (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$
                      Inlines -> Blocks
B.plain (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.image Text
url Text
"" Inlines
forall a. Monoid a => a
mempty
             Maybe Text
_ -> Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith (Text
"",[Text
"iframe"],[(Text
"src", Text
url)]) (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ Blocks
forall a. Monoid a => a
mempty)
       (\PandocError
e -> do
         LogMessage -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> LogMessage
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ Text -> Text -> LogMessage
CouldNotFetchResource Text
url (PandocError -> Text
renderError PandocError
e)
         Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Text -> TagParser m a
ignore (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ [Tag Text] -> Text
renderTags' [Tag Text
tag, Text -> Tag Text
forall str. str -> Tag str
TagClose Text
"iframe"])
pRawHtmlBlock :: PandocMonad m => TagParser m Blocks
pRawHtmlBlock :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pRawHtmlBlock = do
  Text
raw <- Text -> TagParser m Text
forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
pHtmlBlock Text
"script" TagParser m Text -> TagParser m Text -> TagParser m Text
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> TagParser m Text
forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
pHtmlBlock Text
"style" TagParser m Text -> TagParser m Text -> TagParser m Text
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> TagParser m Text
forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
pHtmlBlock Text
"textarea"
          TagParser m Text -> TagParser m Text -> TagParser m Text
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TagParser m Text
forall (m :: * -> *). PandocMonad m => TagParser m Text
pRawTag
  Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
forall s (m :: * -> *) t b.
Stream s m t =>
(ReaderOptions -> b) -> ParsecT s HTMLState m b
getOption ReaderOptions -> Extensions
readerExtensions
  if Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_raw_html Extensions
exts Bool -> Bool -> Bool
&& Bool -> Bool
not (Text -> Bool
T.null Text
raw)
     then Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TagParser m Blocks) -> Blocks -> TagParser m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Blocks
B.rawBlock Text
"html" Text
raw
     else Text -> TagParser m Blocks
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Text -> TagParser m a
ignore Text
raw
ignore :: (Monoid a, PandocMonad m) => Text -> TagParser m a
ignore :: forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Text -> TagParser m a
ignore Text
raw = do
  SourcePos
pos <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  
  
  Bool
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Bool
T.null Text
raw) (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$
    LogMessage -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> LogMessage
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent Text
raw SourcePos
pos
  a -> TagParser m a
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty
pHtmlBlock :: PandocMonad m => Text -> TagParser m Text
pHtmlBlock :: forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
pHtmlBlock Text
t = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
forall a b. (a -> b) -> a -> b
$ do
  Tag Text
open <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
t [])
  [Tag Text]
contents <- TagParser m (Tag Text)
-> TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill TagParser m (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny ((Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> Tag Text -> Bool
matchTagClose Text
t))
  Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text)
-> Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
forall a b. (a -> b) -> a -> b
$ [Tag Text] -> Text
renderTags' ([Tag Text] -> Text) -> [Tag Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Tag Text
open] [Tag Text] -> [Tag Text] -> [Tag Text]
forall a. Semigroup a => a -> a -> a
<> [Tag Text]
contents [Tag Text] -> [Tag Text] -> [Tag Text]
forall a. Semigroup a => a -> a -> a
<> [Text -> Tag Text
forall str. str -> Tag str
TagClose Text
t]
eSection :: PandocMonad m => TagParser m Blocks
eSection :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
eSection = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  let matchChapter :: [(a, Text)] -> Bool
matchChapter [(a, Text)]
as = Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Text -> Text -> Bool
T.isInfixOf Text
"chapter")
                        (a -> [(a, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup a
"type" [(a, Text)]
as Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> [(a, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup a
"epub:type" [(a, Text)]
as)
  let sectTag :: Tag Text -> Bool
sectTag = (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
sectioningContent) [Attribute Text] -> Bool
forall {a}. (Eq a, IsString a) => [(a, Text)] -> Bool
matchChapter
  TagOpen Text
tag [Attribute Text]
_ <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy Tag Text -> Bool
sectTag
  ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) s a.
PandocMonad m =>
HTMLParser m s a -> HTMLParser m s a
setInChapter (Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
tag ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block)
headerLevel :: Text -> TagParser m Int
 Text
tagtype =
  case Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Int -> Text -> Text
T.drop Int
1 Text
tagtype) of
        Just Int
level ->
              Int -> TagParser m Int
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
level
        Maybe Int
Nothing -> String -> TagParser m Int
forall a.
String -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail String
"Could not retrieve header level"
eTitlePage :: PandocMonad m => TagParser m ()
eTitlePage :: forall (m :: * -> *). PandocMonad m => TagParser m ()
eTitlePage = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ do
  let isTitlePage :: [(a, Text)] -> Bool
isTitlePage [(a, Text)]
as = Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Text -> Text -> Bool
T.isInfixOf Text
"titlepage")
       (a -> [(a, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup a
"type" [(a, Text)]
as Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> [(a, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup a
"epub:type" [(a, Text)]
as)
  let groupTag :: Tag Text -> Bool
groupTag = (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (\Text
x -> Text
x Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
groupingContent Bool -> Bool -> Bool
|| Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"section")
                          [Attribute Text] -> Bool
forall {a}. (Eq a, IsString a) => [(a, Text)] -> Bool
isTitlePage
  TagOpen Text
tag [Attribute Text]
_ <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy Tag Text -> Bool
groupTag
  () ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b.
a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
tag ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
pHeader :: PandocMonad m => TagParser m Blocks
 = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  TagOpen Text
tagtype [Attribute Text]
attr' <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$
                           (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"h1",Text
"h2",Text
"h3",Text
"h4",Text
"h5",Text
"h6"])
                           (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  let attr :: [Attribute Text]
attr = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attr'
  Int
level <- Text -> TagParser m Int
forall (m :: * -> *). Text -> TagParser m Int
headerLevel Text
tagtype
  Inlines
contents <- Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
tagtype ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
  let ident :: Text
ident = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [Attribute Text]
attr
  let classes :: [Text]
classes = [Text] -> (Text -> [Text]) -> Maybe Text -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Text -> [Text]
T.words (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Attribute Text]
attr
  let keyvals :: [Attribute Text]
keyvals = [(Text
k,Text
v) | (Text
k,Text
v) <- [Attribute Text]
attr, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"class", Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"id"]
  Attr
attr'' <- Attr
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
 HasIdentifierList st) =>
Attr -> Inlines -> ParsecT s st m Attr
registerHeader (Text
ident, [Text]
classes, [Attribute Text]
keyvals) Inlines
contents
  Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Inlines -> Blocks
B.headerWith Attr
attr'' Int
level Inlines
contents
pHrule :: PandocMonad m => TagParser m Blocks
pHrule :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pHrule = do
  (Text -> Bool)
-> ([Attribute Text] -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Text -> Bool)
-> ([Attribute Text] -> Bool) -> TagParser m (Tag Text)
pSelfClosing (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"hr") (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  Bool
inNotes <- HTMLState -> Bool
inFootnotes (HTMLState -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TagParser m Blocks) -> Blocks -> TagParser m Blocks
forall a b. (a -> b) -> a -> b
$ if Bool
inNotes
              then Blocks
forall a. Monoid a => a
mempty
              else Blocks
B.horizontalRule
pBlockQuote :: PandocMonad m => TagParser m Blocks
pBlockQuote :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pBlockQuote = do
  Blocks
contents <- Text -> TagParser m Blocks -> TagParser m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"blockquote" TagParser m Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block
  Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TagParser m Blocks) -> Blocks -> TagParser m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks
B.blockQuote (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ Bool -> Blocks -> Blocks
fixPlains Bool
False Blocks
contents
pPlain :: PandocMonad m => TagParser m Blocks
pPlain :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pPlain = do
  Inlines
contents <- HTMLParser m [Tag Text] Inlines -> HTMLParser m [Tag Text] Inlines
forall (m :: * -> *) s a.
PandocMonad m =>
HTMLParser m s a -> HTMLParser m s a
setInPlain (HTMLParser m [Tag Text] Inlines
 -> HTMLParser m [Tag Text] Inlines)
-> HTMLParser m [Tag Text] Inlines
-> HTMLParser m [Tag Text] Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
-> HTMLParser m [Tag Text] Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HTMLParser m [Tag Text] Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 HTMLParser m [Tag Text] Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline
  if Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
contents
     then Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
     else Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TagParser m Blocks) -> Blocks -> TagParser m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.plain Inlines
contents
pPara :: PandocMonad m => TagParser m Blocks
pPara :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pPara = do
  Inlines
contents <- Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"p" ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline
  (do Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_empty_paragraphs
      Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
contents)
      Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty)
    TagParser m Blocks -> TagParser m Blocks -> TagParser m Blocks
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Blocks
B.para Inlines
contents)
pFigure :: PandocMonad m => TagParser m Blocks
pFigure :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pFigure = do
  TagOpen Text
tag [Attribute Text]
attrList <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"figure" []
  let parser :: ParsecT
  [Tag Text] HTMLState (ReaderT HTMLLocal m) (Either Blocks Blocks)
parser = Blocks -> Either Blocks Blocks
forall a b. a -> Either a b
Left (Blocks -> Either Blocks Blocks)
-> TagParser m Blocks
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Either Blocks Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> TagParser m Blocks -> TagParser m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"figcaption" TagParser m Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block ParsecT
  [Tag Text] HTMLState (ReaderT HTMLLocal m) (Either Blocks Blocks)
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Either Blocks Blocks)
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Either Blocks Blocks)
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
             (Blocks -> Either Blocks Blocks
forall a b. b -> Either a b
Right (Blocks -> Either Blocks Blocks)
-> TagParser m Blocks
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) (Either Blocks Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TagParser m Blocks
forall (m :: * -> *). PandocMonad m => TagParser m Blocks
block)
  ([Blocks]
captions, [Blocks]
rest) <- [Either Blocks Blocks] -> ([Blocks], [Blocks])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ([Either Blocks Blocks] -> ([Blocks], [Blocks]))
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) [Either Blocks Blocks]
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) ([Blocks], [Blocks])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
  [Tag Text] HTMLState (ReaderT HTMLLocal m) (Either Blocks Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT
     [Tag Text] HTMLState (ReaderT HTMLLocal m) [Either Blocks Blocks]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT
  [Tag Text] HTMLState (ReaderT HTMLLocal m) (Either Blocks Blocks)
parser (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
tag ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
  
  Blocks -> TagParser m Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TagParser m Blocks) -> Blocks -> TagParser m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Caption -> Blocks -> Blocks
B.figureWith ([Attribute Text] -> Attr
toAttr [Attribute Text]
attrList)
                        (Blocks -> Caption
B.simpleCaption ([Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
captions))
                        ([Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
rest)
pCodeBlock :: PandocMonad m => TagParser m Blocks
pCodeBlock :: forall (m :: * -> *). PandocMonad m => TagParser m Blocks
pCodeBlock = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ do
  TagOpen Text
_ [Attribute Text]
attr' <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"pre" [])
  
  
  Attr
attr <- case [Attribute Text]
attr' of
    Attribute Text
_:[Attribute Text]
_ -> Attr -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Attribute Text] -> Attr
toAttr [Attribute Text]
attr')
    []  -> Attr
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Attr
nullAttr (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
forall a b. (a -> b) -> a -> b
$ do
      TagOpen Text
_ [Attribute Text]
codeAttr <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"code" [])
      Attr -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Attr -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr)
-> Attr -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Attr
forall a b. (a -> b) -> a -> b
$ [Attribute Text] -> Attr
toAttr
        [ (Text
k, Text
v') | (Text
k, Text
v) <- [Attribute Text]
codeAttr
                    
                  , let v' :: Text
v' = if Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"class"
                             then Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
v (Text -> Text -> Maybe Text
T.stripPrefix Text
"language-" Text
v)
                             else Text
v ]
  [Tag Text]
contents <- TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill TagParser m (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"pre" ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
  let rawText :: Text
rawText = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Text) -> [Tag Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Tag Text -> Text
tagToText [Tag Text]
contents
  
  let result' :: Text
result' = case Text -> Maybe (Char, Text)
T.uncons Text
rawText of
                     Just (Char
'\n', Text
xs) -> Text
xs
                     Maybe (Char, Text)
_               -> Text
rawText
  
  let result :: Text
result = case Text -> Maybe (Text, Char)
T.unsnoc Text
result' of
                    Just (Text
result'', Char
'\n') -> Text
result''
                    Maybe (Text, Char)
_                     -> Text
result'
  Blocks -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks)
-> Blocks
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Blocks
B.codeBlockWith Attr
attr Text
result
tagToText :: Tag Text -> Text
tagToText :: Tag Text -> Text
tagToText (TagText Text
s)      = Text
s
tagToText (TagOpen Text
"br" [Attribute Text]
_) = Text
"\n"
tagToText Tag Text
_                = Text
""
inline :: PandocMonad m => TagParser m Inlines
inline :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline = TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pTagText TagParser m Inlines -> TagParser m Inlines -> TagParser m Inlines
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> do
  Tag Text
tag <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ((Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy Tag Text -> Bool
isInlineTag)
  Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
forall s (m :: * -> *) t b.
Stream s m t =>
(ReaderOptions -> b) -> ParsecT s HTMLState m b
getOption ReaderOptions -> Extensions
readerExtensions
  case Tag Text
tag of
    TagOpen Text
name [Attribute Text]
attr ->
      case Text
name of
        Text
"a" | Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_epub_html_exts Extensions
exts
          , Just Text
"noteref" <- Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attr Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"epub:type" [Attribute Text]
attr
          , Just (Char
'#',Text
_) <- Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"href" [Attribute Text]
attr Maybe Text -> (Text -> Maybe (Char, Text)) -> Maybe (Char, Text)
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe (Char, Text)
T.uncons
            -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
eNoteref
            | Bool
otherwise -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pLink
        Text
"switch" -> (Inlines -> Inlines) -> TagParser m Inlines -> TagParser m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
(Inlines -> a) -> TagParser m a -> TagParser m a
eSwitch Inlines -> Inlines
forall a. a -> a
id TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline
        Text
"q" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pQ
        Text
"em" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pEmph
        Text
"i"  -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pEmph
        Text
"strong" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pStrong
        Text
"b" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pStrong
        Text
"sup" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSuperscript
        Text
"sub" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSubscript
        Text
"small" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSmall
        Text
"s" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pStrikeout
        Text
"strike" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pStrikeout
        Text
"del" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pStrikeout
        Text
"u" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pUnderline
        Text
"ins" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pUnderline
        Text
"br" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pLineBreak
        Text
"img" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pImage
        Text
"svg" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSvg
        Text
"bdo" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pBdo
        Text
"tt" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pCode
        Text
"code" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pCode
        Text
"samp" -> Text -> Text -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> TagParser m Inlines
pCodeWithClass Text
"samp" Text
"sample"
        Text
"var" -> Text -> Text -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> TagParser m Inlines
pCodeWithClass Text
"var" Text
"variable"
        Text
"span" -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSpan
        Text
"math" -> Bool -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => Bool -> TagParser m Inlines
pMath Bool
False
        Text
"input"
          | Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attr Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"checkbox"
          -> (HTMLLocal -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks HTMLLocal -> Bool
inListItem ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool
-> (Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> (a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> TagParser m Inlines -> TagParser m Inlines
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pCheckbox
        Text
"script"
          | Just Text
x <- Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attr
          , Text
"math/tex" Text -> Text -> Bool
`T.isPrefixOf` Text
x -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pScriptMath
        Text
_ | Text
name Text -> Set Text -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Set Text
htmlSpanLikeElements -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSpanLike
        Text
_ -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pRawHtmlInline
    TagText Text
_ -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pTagText
    Tag Text
_ -> TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pRawHtmlInline
pSelfClosing :: PandocMonad m
             => (Text -> Bool) -> ([Attribute Text] -> Bool)
             -> TagParser m (Tag Text)
pSelfClosing :: forall (m :: * -> *).
PandocMonad m =>
(Text -> Bool)
-> ([Attribute Text] -> Bool) -> TagParser m (Tag Text)
pSelfClosing Text -> Bool
f [Attribute Text] -> Bool
g = do
  Tag Text
open <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen Text -> Bool
f [Attribute Text] -> Bool
g)
  TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (TagParser m (Tag Text)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Text -> Bool) -> Tag Text -> Bool
forall str. (str -> Bool) -> Tag str -> Bool
tagClose Text -> Bool
f)
  Tag Text -> TagParser m (Tag Text)
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Tag Text
open
pQ :: PandocMonad m => TagParser m Inlines
pQ :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pQ = do
  TagOpen Text
_ [Attribute Text]
attrs <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ Text -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
Eq str =>
str -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpenLit Text
"q" (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"cite" [Attribute Text]
attrs of
    Just Text
url -> do
      let uid :: Text
uid = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$
                   Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"name" [Attribute Text]
attrs Maybe Text -> Maybe Text -> Maybe Text
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [Attribute Text]
attrs
      let cls :: [Text]
cls = [Text] -> (Text -> [Text]) -> Maybe Text -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Text -> [Text]
T.words (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Attribute Text]
attrs
      Text
url' <- Text -> TagParser m Text
forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
canonicalizeUrl Text
url
      (Inlines -> Inlines) -> TagParser m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
makeQuote ((Inlines -> Inlines) -> TagParser m Inlines)
-> (Inlines -> Inlines) -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
B.spanWith (Text
uid, [Text]
cls, [(Text
"cite", Text -> Text
escapeURI Text
url')])
    Maybe Text
Nothing -> (Inlines -> Inlines) -> TagParser m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
makeQuote Inlines -> Inlines
forall a. a -> a
id
 where
  makeQuote :: (Inlines -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
makeQuote Inlines -> Inlines
wrapper = do
    QuoteContext
ctx <- (HTMLLocal -> QuoteContext)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) QuoteContext
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks HTMLLocal -> QuoteContext
quoteContext
    let (Inlines -> Inlines
constructor, QuoteContext
innerContext) = case QuoteContext
ctx of
                  QuoteContext
InDoubleQuote -> (Inlines -> Inlines
B.singleQuoted, QuoteContext
InSingleQuote)
                  QuoteContext
_             -> (Inlines -> Inlines
B.doubleQuoted, QuoteContext
InDoubleQuote)
    Inlines
content <- QuoteContext
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s a.
QuoteContext
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
-> ParsecT s HTMLState (ReaderT HTMLLocal m) a
forall st (m :: * -> *) s a.
HasQuoteContext st m =>
QuoteContext -> ParsecT s st m a -> ParsecT s st m a
withQuoteContext QuoteContext
innerContext
                  ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"q"))
    Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Inlines -> Inlines
constructor (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
wrapper) Inlines
content
pEmph :: PandocMonad m => TagParser m Inlines
pEmph :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pEmph = Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"em" Inlines -> Inlines
B.emph TagParser m Inlines -> TagParser m Inlines -> TagParser m Inlines
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"i" Inlines -> Inlines
B.emph
pStrong :: PandocMonad m => TagParser m Inlines
pStrong :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pStrong = Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"strong" Inlines -> Inlines
B.strong TagParser m Inlines -> TagParser m Inlines -> TagParser m Inlines
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"b" Inlines -> Inlines
B.strong
pSuperscript :: PandocMonad m => TagParser m Inlines
pSuperscript :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSuperscript = Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"sup" Inlines -> Inlines
B.superscript
pSubscript :: PandocMonad m => TagParser m Inlines
pSubscript :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSubscript = Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"sub" Inlines -> Inlines
B.subscript
pSpanLike :: PandocMonad m => TagParser m Inlines
pSpanLike :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSpanLike =
  (Text -> TagParser m Inlines -> TagParser m Inlines)
-> TagParser m Inlines -> Set Text -> TagParser m Inlines
forall a b. (a -> b -> b) -> b -> Set a -> b
Set.foldr
    (\Text
tagName TagParser m Inlines
acc -> TagParser m Inlines
acc TagParser m Inlines -> TagParser m Inlines -> TagParser m Inlines
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> TagParser m Inlines
forall {m :: * -> *}.
PandocMonad m =>
Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
parseTag Text
tagName)
    TagParser m Inlines
forall a. ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
    Set Text
htmlSpanLikeElements
  where
    parseTag :: Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
parseTag Text
tagName = do
      TagOpen Text
_ [Attribute Text]
attrs <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ Text -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
Eq str =>
str -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpenLit Text
tagName (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
      let (Text
ids, [Text]
cs, [Attribute Text]
kvs) = [Attribute Text] -> Attr
toAttr [Attribute Text]
attrs
      Inlines
content <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
tagName ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
      Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
B.spanWith (Text
ids, Text
tagName Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
cs, [Attribute Text]
kvs) Inlines
content
pSmall :: PandocMonad m => TagParser m Inlines
pSmall :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSmall = Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"small" (Attr -> Inlines -> Inlines
B.spanWith (Text
"",[Text
"small"],[]))
pStrikeout :: PandocMonad m => TagParser m Inlines
pStrikeout :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pStrikeout =
  Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"s" Inlines -> Inlines
B.strikeout TagParser m Inlines -> TagParser m Inlines -> TagParser m Inlines
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
    Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"strike" Inlines -> Inlines
B.strikeout TagParser m Inlines -> TagParser m Inlines -> TagParser m Inlines
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
    Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"del" Inlines -> Inlines
B.strikeout TagParser m Inlines -> TagParser m Inlines -> TagParser m Inlines
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
    TagParser m Inlines -> TagParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"span" [(Text
"class",Text
"strikeout")])
            Inlines
contents <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
-> TagParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TagParser m Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"span")
            Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TagParser m Inlines) -> Inlines -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.strikeout Inlines
contents)
pUnderline :: PandocMonad m => TagParser m Inlines
pUnderline :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pUnderline = Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"u" Inlines -> Inlines
B.underline TagParser m Inlines -> TagParser m Inlines -> TagParser m Inlines
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> (Inlines -> Inlines) -> TagParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
"ins" Inlines -> Inlines
B.underline
pLineBreak :: PandocMonad m => TagParser m Inlines
pLineBreak :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pLineBreak = do
  (Text -> Bool)
-> ([Attribute Text] -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Text -> Bool)
-> ([Attribute Text] -> Bool) -> TagParser m (Tag Text)
pSelfClosing (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"br") (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.linebreak
pLink :: PandocMonad m => TagParser m Inlines
pLink :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pLink = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ do
  tag :: Tag Text
tag@(TagOpen Text
_ [Attribute Text]
attr') <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ Text -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
Eq str =>
str -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpenLit Text
"a" (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  let title :: Text
title = Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"title" Tag Text
tag
  let attr :: Attr
attr = [Attribute Text] -> Attr
toAttr ([Attribute Text] -> Attr) -> [Attribute Text] -> Attr
forall a b. (a -> b) -> a -> b
$ (Attribute Text -> Bool) -> [Attribute Text] -> [Attribute Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Text
k,Text
_) -> Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"title" Bool -> Bool -> Bool
&& Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"href") [Attribute Text]
attr'
  Inlines
lab <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"a")
  HTMLState
st <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  if HTMLState -> Bool
inFootnotes HTMLState
st Bool -> Bool -> Bool
&& Text -> Tag Text -> Maybe Text
maybeFromAttrib Text
"role" Tag Text
tag Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"doc-backlink"
     then Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
     else do
       
       case Text -> Tag Text -> Maybe Text
maybeFromAttrib Text
"href" Tag Text
tag of
            Maybe Text
Nothing   ->
              Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Attr -> Inlines -> Inlines
B.spanWith Attr
attr) Inlines
lab
            Just Text
url' -> do
              Text
url <- Text -> TagParser m Text
forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
canonicalizeUrl Text
url'
              Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces
                        (Attr -> Text -> Text -> Inlines -> Inlines
B.linkWith Attr
attr (Text -> Text
escapeURI Text
url) Text
title) Inlines
lab
pImage :: PandocMonad m => TagParser m Inlines
pImage :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pImage = do
  tag :: Tag Text
tag@(TagOpen Text
_ [Attribute Text]
attr') <- (Text -> Bool)
-> ([Attribute Text] -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Text -> Bool)
-> ([Attribute Text] -> Bool) -> TagParser m (Tag Text)
pSelfClosing (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"img") (Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Text -> Bool)
-> ([Attribute Text] -> Maybe Text) -> [Attribute Text] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"src")
  Text
url <- Text -> TagParser m Text
forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
canonicalizeUrl (Text -> TagParser m Text) -> Text -> TagParser m Text
forall a b. (a -> b) -> a -> b
$ Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"src" Tag Text
tag
  let title :: Text
title = Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"title" Tag Text
tag
  let alt :: Text
alt = Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"alt" Tag Text
tag
  let attr :: Attr
attr = [Attribute Text] -> Attr
toAttr ([Attribute Text] -> Attr) -> [Attribute Text] -> Attr
forall a b. (a -> b) -> a -> b
$ (Attribute Text -> Bool) -> [Attribute Text] -> [Attribute Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Text
k,Text
_) -> Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"alt" Bool -> Bool -> Bool
&& Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"title" Bool -> Bool -> Bool
&& Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"src") [Attribute Text]
attr'
  Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TagParser m Inlines) -> Inlines -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith Attr
attr (Text -> Text
escapeURI Text
url) Text
title (Text -> Inlines
B.text Text
alt)
pSvg :: PandocMonad m => TagParser m Inlines
pSvg :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSvg = do
  Extension -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_raw_html
  
  opent :: Tag Text
opent@(TagOpen Text
_ [Attribute Text]
attr') <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> [Attribute Text] -> Tag Text -> Bool
matchTagOpen Text
"svg" [])
  let (Text
ident,[Text]
cls,[Attribute Text]
_) = [Attribute Text] -> Attr
toAttr [Attribute Text]
attr'
  [Tag Text]
contents <- TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"svg") ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> TagParser m (Tag Text) -> TagParser m (Tag Text)
forall a b.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TagParser m (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny)
  Tag Text
closet <- Text -> Tag Text
forall str. str -> Tag str
TagClose Text
"svg" Tag Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> TagParser m (Tag Text)
forall a b.
a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) b
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
"svg" ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof)
  let rawText :: Text
rawText = Text -> Text
T.strip (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Tag Text] -> Text
renderTags' (Tag Text
opent Tag Text -> [Tag Text] -> [Tag Text]
forall a. a -> [a] -> [a]
: [Tag Text]
contents [Tag Text] -> [Tag Text] -> [Tag Text]
forall a. [a] -> [a] -> [a]
++ [Tag Text
closet])
  let svgData :: Text
svgData = Text
"data:image/svg+xml;base64," Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
                   ByteString -> Text
UTF8.toText (ByteString -> ByteString
encode (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
UTF8.fromText Text
rawText)
  Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TagParser m Inlines) -> Inlines -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith (Text
ident,[Text]
cls,[]) Text
svgData Text
forall a. Monoid a => a
mempty Inlines
forall a. Monoid a => a
mempty
pCodeWithClass :: PandocMonad m => Text -> Text -> TagParser m Inlines
pCodeWithClass :: forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> TagParser m Inlines
pCodeWithClass Text
name Text
class' = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ do
  TagOpen Text
open [Attribute Text]
attr' <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
name) (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  let (Text
ids,[Text]
cs,[Attribute Text]
kvs) = [Attribute Text] -> Attr
toAttr [Attribute Text]
attr'
      cs' :: [Text]
cs'          = Text
class' Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
cs
  Text
-> Attr
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Attr -> TagParser m Inlines
code Text
open (Text
ids,[Text]
cs',[Attribute Text]
kvs)
pCode :: PandocMonad m => TagParser m Inlines
pCode :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pCode = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ do
  (TagOpen Text
open [Attribute Text]
attr') <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"code",Text
"tt"]) (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  let attr :: Attr
attr = [Attribute Text] -> Attr
toAttr [Attribute Text]
attr'
  Text
-> Attr
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Attr -> TagParser m Inlines
code Text
open Attr
attr
code :: PandocMonad m => Text -> Attr -> TagParser m Inlines
code :: forall (m :: * -> *).
PandocMonad m =>
Text -> Attr -> TagParser m Inlines
code Text
open Attr
attr = do
  Inlines
result <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
-> TagParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TagParser m Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline (Text -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (m :: * -> *). PandocMonad m => Text -> TagParser m ()
pCloses Text
open)
  Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TagParser m Inlines) -> Inlines -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
formatCode Attr
attr Inlines
result
pBdo :: PandocMonad m => TagParser m Inlines
pBdo :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pBdo = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ do
  TagOpen Text
_ [Attribute Text]
attr' <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"bdo") (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  let attr :: [Attribute Text]
attr = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attr'
  Inlines
contents <- Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"bdo" ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline
  Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"dir" [Attribute Text]
attr of
    
    Just Text
dir -> Attr -> Inlines -> Inlines
B.spanWith (Text
"", [], [(Text
"dir",Text -> Text
T.toLower Text
dir)]) Inlines
contents
    Maybe Text
Nothing  -> Inlines
contents
pSpan :: PandocMonad m => TagParser m Inlines
pSpan :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pSpan = do
  (TagOpen Text
_ [Attribute Text]
attr') <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ((Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"span") (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True))
  Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
forall s (m :: * -> *) t b.
Stream s m t =>
(ReaderOptions -> b) -> ParsecT s HTMLState m b
getOption ReaderOptions -> Extensions
readerExtensions
  if Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_native_spans Extensions
exts
     then do
       Inlines
contents <- Text -> TagParser m Inlines -> TagParser m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"span" TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline
       let attr :: Attr
attr = [Attribute Text] -> Attr
toAttr [Attribute Text]
attr'
       let classes :: [Text]
classes = [Text] -> (Text -> [Text]) -> Maybe Text -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Text -> [Text]
T.words (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Attribute Text]
attr'
       let styleAttr :: Text
styleAttr   = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"style" [Attribute Text]
attr'
       let fontVariant :: Text
fontVariant = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$
                          [Text] -> Text -> Maybe Text
pickStyleAttrProps [Text
"font-variant"] Text
styleAttr
       let isSmallCaps :: Bool
isSmallCaps = Text
fontVariant Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"small-caps" Bool -> Bool -> Bool
||
                           Text
"smallcaps" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes
       let tag :: Inlines -> Inlines
tag = if Bool
isSmallCaps then Inlines -> Inlines
B.smallcaps else Attr -> Inlines -> Inlines
B.spanWith Attr
attr
       Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TagParser m Inlines) -> Inlines -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
tag Inlines
contents
     else if Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_raw_html Extensions
exts
             then do
               Tag Text
tag <- (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool)
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text))
-> (Tag Text -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"span") (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
               Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TagParser m Inlines) -> Inlines -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines
B.rawInline Text
"html" (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ [Tag Text] -> Text
renderTags' [Tag Text
tag]
             else Text -> TagParser m Inlines -> TagParser m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
"span" TagParser m Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline 
pRawHtmlInline :: PandocMonad m => TagParser m Inlines
pRawHtmlInline :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pRawHtmlInline = do
  Bool
inplain <- (HTMLLocal -> Bool)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks HTMLLocal -> Bool
inPlain
  Tag Text
result <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Text -> Bool) -> Tag Text -> Bool
forall str. (str -> Bool) -> Tag str -> Bool
tagComment (Bool -> Text -> Bool
forall a b. a -> b -> a
const Bool
True))
            TagParser m (Tag Text)
-> TagParser m (Tag Text) -> TagParser m (Tag Text)
forall a.
ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> if Bool
inplain
                   then (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Bool -> Bool
not (Bool -> Bool) -> (Tag Text -> Bool) -> Tag Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tag Text -> Bool
isBlockTag)
                   else (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy Tag Text -> Bool
isInlineTag
  Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
forall s (m :: * -> *) t b.
Stream s m t =>
(ReaderOptions -> b) -> ParsecT s HTMLState m b
getOption ReaderOptions -> Extensions
readerExtensions
  let raw :: Text
raw = [Tag Text] -> Text
renderTags' [Tag Text
result]
  if Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_raw_html Extensions
exts
     then Inlines -> TagParser m Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TagParser m Inlines) -> Inlines -> TagParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines
B.rawInline Text
"html" Text
raw
     else Text -> TagParser m Inlines
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Text -> TagParser m a
ignore Text
raw
mathMLToTeXMath :: Text -> Either Text Text
mathMLToTeXMath :: Text -> Either Text Text
mathMLToTeXMath Text
s = [Exp] -> Text
writeTeX ([Exp] -> Text) -> Either Text [Exp] -> Either Text Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either Text [Exp]
readMathML Text
s
pScriptMath :: PandocMonad m => TagParser m Inlines
pScriptMath :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pScriptMath = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ do
  TagOpen Text
_ [Attribute Text]
attr' <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"script") (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  Bool
isdisplay <- case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"type" [Attribute Text]
attr' of
                    Just Text
x | Text
"math/tex" Text -> Text -> Bool
`T.isPrefixOf` Text
x
                      -> Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool)
-> Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool
forall a b. (a -> b) -> a -> b
$ Text
"display" Text -> Text -> Bool
`T.isSuffixOf` Text
x
                    Maybe Text
_ -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Bool
forall a. ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  Text
contents <- [Tag Text] -> Text
forall str. StringLike str => [Tag str] -> str
innerText ([Tag Text] -> Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TagParser m (Tag Text)
-> TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill TagParser m (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny ((Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> Tag Text -> Bool
matchTagClose Text
"script"))
  Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ (if Bool
isdisplay then Text -> Inlines
B.displayMath else Text -> Inlines
B.math) Text
contents
pMath :: PandocMonad m => Bool -> TagParser m Inlines
pMath :: forall (m :: * -> *). PandocMonad m => Bool -> TagParser m Inlines
pMath Bool
inCase = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ do
  open :: Tag Text
open@(TagOpen Text
_ [Attribute Text]
attr') <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy ((Tag Text -> Bool) -> TagParser m (Tag Text))
-> (Tag Text -> Bool) -> TagParser m (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> ([Attribute Text] -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"math") (Bool -> [Attribute Text] -> Bool
forall a b. a -> b -> a
const Bool
True)
  
  
  let attr :: [Attribute Text]
attr = [Attribute Text] -> [Attribute Text]
toStringAttr [Attribute Text]
attr'
  Bool
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
inCase (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ())
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall a b. (a -> b) -> a -> b
$
    Bool -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
mathMLNamespace) (Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"xmlns" [Attribute Text]
attr))
  [Tag Text]
contents <- TagParser m (Tag Text)
-> TagParser m (Tag Text)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) [Tag Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill TagParser m (Tag Text)
forall (m :: * -> *). PandocMonad m => TagParser m (Tag Text)
pAny ((Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy (Text -> Tag Text -> Bool
matchTagClose Text
"math"))
  case Text -> Either Text Text
mathMLToTeXMath ([Tag Text] -> Text
forall str. StringLike str => [Tag str] -> str
renderTags ([Tag Text] -> Text) -> [Tag Text] -> Text
forall a b. (a -> b) -> a -> b
$
          [Tag Text
open] [Tag Text] -> [Tag Text] -> [Tag Text]
forall a. Semigroup a => a -> a -> a
<> [Tag Text]
contents [Tag Text] -> [Tag Text] -> [Tag Text]
forall a. Semigroup a => a -> a -> a
<> [Text -> Tag Text
forall str. str -> Tag str
TagClose Text
"math"]) of
       Left Text
_   -> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
B.spanWith (Text
"",[Text
"math"],[Attribute Text]
attr) (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$
                             [Tag Text] -> Text
forall str. StringLike str => [Tag str] -> str
innerText [Tag Text]
contents
       Right Text
"" -> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
       Right Text
x  -> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"display" [Attribute Text]
attr of
                                 Just Text
"block" -> Text -> Inlines
B.displayMath Text
x
                                 Maybe Text
_            -> Text -> Inlines
B.math Text
x
pInlinesInTags :: PandocMonad m => Text -> (Inlines -> Inlines)
               -> TagParser m Inlines
pInlinesInTags :: forall (m :: * -> *).
PandocMonad m =>
Text -> (Inlines -> Inlines) -> TagParser m Inlines
pInlinesInTags Text
tagtype Inlines -> Inlines
f = (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
f (Inlines -> Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
Text -> TagParser m a -> TagParser m a
pInTags Text
tagtype ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => TagParser m Inlines
inline
pTagText :: PandocMonad m => TagParser m Inlines
pTagText :: forall (m :: * -> *). PandocMonad m => TagParser m Inlines
pTagText = ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ do
  SourcePos
pos <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  (TagText Text
str) <- (Tag Text -> Bool) -> TagParser m (Tag Text)
forall (m :: * -> *).
PandocMonad m =>
(Tag Text -> Bool) -> TagParser m (Tag Text)
pSatisfy Tag Text -> Bool
forall str. Tag str -> Bool
isTagText
  HTMLState
st <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  HTMLLocal
qu <- ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLLocal
forall r (m :: * -> *). MonadReader r m => m r
ask
  Either ParseError [Inlines]
parsed <- ReaderT HTMLLocal m (Either ParseError [Inlines])
-> ParsecT
     [Tag Text]
     HTMLState
     (ReaderT HTMLLocal m)
     (Either ParseError [Inlines])
forall (m :: * -> *) a.
Monad m =>
m a -> ParsecT [Tag Text] HTMLState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT HTMLLocal m (Either ParseError [Inlines])
 -> ParsecT
      [Tag Text]
      HTMLState
      (ReaderT HTMLLocal m)
      (Either ParseError [Inlines]))
-> ReaderT HTMLLocal m (Either ParseError [Inlines])
-> ParsecT
     [Tag Text]
     HTMLState
     (ReaderT HTMLLocal m)
     (Either ParseError [Inlines])
forall a b. (a -> b) -> a -> b
$ m (Either ParseError [Inlines])
-> ReaderT HTMLLocal m (Either ParseError [Inlines])
forall (m :: * -> *) a. Monad m => m a -> ReaderT HTMLLocal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either ParseError [Inlines])
 -> ReaderT HTMLLocal m (Either ParseError [Inlines]))
-> m (Either ParseError [Inlines])
-> ReaderT HTMLLocal m (Either ParseError [Inlines])
forall a b. (a -> b) -> a -> b
$
            (ReaderT HTMLLocal m (Either ParseError [Inlines])
 -> HTMLLocal -> m (Either ParseError [Inlines]))
-> HTMLLocal
-> ReaderT HTMLLocal m (Either ParseError [Inlines])
-> m (Either ParseError [Inlines])
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT HTMLLocal m (Either ParseError [Inlines])
-> HTMLLocal -> m (Either ParseError [Inlines])
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT HTMLLocal
qu (ReaderT HTMLLocal m (Either ParseError [Inlines])
 -> m (Either ParseError [Inlines]))
-> ReaderT HTMLLocal m (Either ParseError [Inlines])
-> m (Either ParseError [Inlines])
forall a b. (a -> b) -> a -> b
$ ParsecT Sources HTMLState (ReaderT HTMLLocal m) [Inlines]
-> HTMLState
-> String
-> Sources
-> ReaderT HTMLLocal m (Either ParseError [Inlines])
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> String -> s -> m (Either ParseError a)
runParserT (ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pTagContents) HTMLState
st String
"text"
               ([(SourcePos, Text)] -> Sources
Sources [(SourcePos
pos, Text
str)])
  case Either ParseError [Inlines]
parsed of
       Left ParseError
_        -> PandocError
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a.
PandocError -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> PandocError
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocParseError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$
                        Text
"Could not parse `" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
str Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'"
       Right [Inlines]
result  -> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
 -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines)
-> Inlines
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) Inlines
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat [Inlines]
result
type InlinesParser m = HTMLParser m Sources
pTagContents :: PandocMonad m => InlinesParser m Inlines
pTagContents :: forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pTagContents =
      Text -> Inlines
B.displayMath (Text -> Inlines)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Text
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Text
forall st s (m :: * -> *).
(HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
mathDisplay
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a.
ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Inlines
B.math        (Text -> Inlines)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Text
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Text
forall st s (m :: * -> *).
(HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
mathInline
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a.
ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pStr
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a.
ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pSpace
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a.
ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall st (m :: * -> *) s.
(HasReaderOptions st, HasLastStrPosition st, HasQuoteContext st m,
 Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines -> ParsecT s st m Inlines
smartPunctuation ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pTagContents
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a.
ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pRawTeX
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a.
ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pSymbol
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a.
ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pBad
pRawTeX :: PandocMonad m => InlinesParser m Inlines
pRawTeX :: forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pRawTeX = do
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
 -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall a b. (a -> b) -> a -> b
$ ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
 -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall a b. (a -> b) -> a -> b
$ do
    Char -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\\'
    [ParsecT Sources HTMLState (ReaderT HTMLLocal m) String]
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ([ParsecT Sources HTMLState (ReaderT HTMLLocal m) String]
 -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String)
-> [ParsecT Sources HTMLState (ReaderT HTMLLocal m) String]
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall a b. (a -> b) -> a -> b
$ (String -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String)
-> [String]
-> [ParsecT Sources HTMLState (ReaderT HTMLLocal m) String]
forall a b. (a -> b) -> [a] -> [b]
map (ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
 -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String)
-> (String
    -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String)
-> String
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string) [String
"begin", String
"eqref", String
"ref"]
  Extension -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_tex
  Sources
inp <- ParsecT Sources HTMLState (ReaderT HTMLLocal m) Sources
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
  HTMLState
st <- ParsecT Sources HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Either ParseError (Attribute Text)
res <- ReaderT HTMLLocal m (Either ParseError (Attribute Text))
-> ParsecT
     Sources
     HTMLState
     (ReaderT HTMLLocal m)
     (Either ParseError (Attribute Text))
forall (m :: * -> *) a.
Monad m =>
m a -> ParsecT Sources HTMLState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT HTMLLocal m (Either ParseError (Attribute Text))
 -> ParsecT
      Sources
      HTMLState
      (ReaderT HTMLLocal m)
      (Either ParseError (Attribute Text)))
-> ReaderT HTMLLocal m (Either ParseError (Attribute Text))
-> ParsecT
     Sources
     HTMLState
     (ReaderT HTMLLocal m)
     (Either ParseError (Attribute Text))
forall a b. (a -> b) -> a -> b
$ ParsecT Sources HTMLState (ReaderT HTMLLocal m) (Attribute Text)
-> HTMLState
-> String
-> Sources
-> ReaderT HTMLLocal m (Either ParseError (Attribute Text))
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> String -> s -> m (Either ParseError a)
runParserT (ParsecT Sources HTMLState (ReaderT HTMLLocal m) Text
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) (Attribute Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw ParsecT Sources HTMLState (ReaderT HTMLLocal m) Text
forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
ParsecT Sources s m Text
rawLaTeXInline) HTMLState
st String
"chunk" Sources
inp
  case Either ParseError (Attribute Text)
res of
       Left ParseError
_                -> InlinesParser m Inlines
forall a. ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
       Right (Text
contents, Text
raw) -> do
         String
_ <- Int
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count (Text -> Int
T.length Text
raw) ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
         Inlines -> InlinesParser m Inlines
forall a. a -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> InlinesParser m Inlines)
-> Inlines -> InlinesParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines
B.rawInline Text
"tex" Text
contents
pStr :: PandocMonad m => InlinesParser m Inlines
pStr :: forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pStr = do
  String
result <- ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
 -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall a b. (a -> b) -> a -> b
$ (Char -> Bool)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy ((Char -> Bool)
 -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char)
-> (Char -> Bool)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
forall a b. (a -> b) -> a -> b
$ \Char
c ->
                     Bool -> Bool
not (Char -> Bool
isSpace Char
c) Bool -> Bool -> Bool
&& Bool -> Bool
not (Char -> Bool
isSpecial Char
c) Bool -> Bool -> Bool
&& Bool -> Bool
not (Char -> Bool
isBad Char
c)
  ParsecT Sources HTMLState (ReaderT HTMLLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos
  Inlines -> InlinesParser m Inlines
forall a. a -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> InlinesParser m Inlines)
-> Inlines -> InlinesParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
result
isSpecial :: Char -> Bool
isSpecial :: Char -> Bool
isSpecial Char
'"'     = Bool
True
isSpecial Char
'\''    = Bool
True
isSpecial Char
'.'     = Bool
True
isSpecial Char
'-'     = Bool
True
isSpecial Char
'$'     = Bool
True
isSpecial Char
'\\'    = Bool
True
isSpecial Char
'\8216' = Bool
True
isSpecial Char
'\8217' = Bool
True
isSpecial Char
'\8220' = Bool
True
isSpecial Char
'\8221' = Bool
True
isSpecial Char
_       = Bool
False
pSymbol :: PandocMonad m => InlinesParser m Inlines
pSymbol :: forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pSymbol = Text -> Inlines
B.str (Text -> Inlines) -> (Char -> Text) -> Char -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton (Char -> Inlines)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Bool)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isSpecial
isBad :: Char -> Bool
isBad :: Char -> Bool
isBad Char
c = Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\128' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\159' 
pBad :: PandocMonad m => InlinesParser m Inlines
pBad :: forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pBad = do
  Char
c <- (Char -> Bool)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isBad
  let c' :: Char
c' = case Char
c of
                Char
'\128' -> Char
'\8364'
                Char
'\130' -> Char
'\8218'
                Char
'\131' -> Char
'\402'
                Char
'\132' -> Char
'\8222'
                Char
'\133' -> Char
'\8230'
                Char
'\134' -> Char
'\8224'
                Char
'\135' -> Char
'\8225'
                Char
'\136' -> Char
'\710'
                Char
'\137' -> Char
'\8240'
                Char
'\138' -> Char
'\352'
                Char
'\139' -> Char
'\8249'
                Char
'\140' -> Char
'\338'
                Char
'\142' -> Char
'\381'
                Char
'\145' -> Char
'\8216'
                Char
'\146' -> Char
'\8217'
                Char
'\147' -> Char
'\8220'
                Char
'\148' -> Char
'\8221'
                Char
'\149' -> Char
'\8226'
                Char
'\150' -> Char
'\8211'
                Char
'\151' -> Char
'\8212'
                Char
'\152' -> Char
'\732'
                Char
'\153' -> Char
'\8482'
                Char
'\154' -> Char
'\353'
                Char
'\155' -> Char
'\8250'
                Char
'\156' -> Char
'\339'
                Char
'\158' -> Char
'\382'
                Char
'\159' -> Char
'\376'
                Char
_      -> Char
'?'
  Inlines -> InlinesParser m Inlines
forall a. a -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> InlinesParser m Inlines)
-> Inlines -> InlinesParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
c'
pSpace :: PandocMonad m => InlinesParser m Inlines
pSpace :: forall (m :: * -> *). PandocMonad m => InlinesParser m Inlines
pSpace = ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isSpace) ParsecT Sources HTMLState (ReaderT HTMLLocal m) String
-> (String
    -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a b.
ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
-> (a -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) b)
-> ParsecT Sources HTMLState (ReaderT HTMLLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
xs ->
            if Char
'\n' Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
xs
               then Inlines -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.softbreak
               else Inlines -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) Inlines
forall a. a -> ParsecT Sources HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
getTagName :: Tag Text -> Maybe Text
getTagName :: Tag Text -> Maybe Text
getTagName (TagOpen Text
t [Attribute Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
getTagName (TagClose Text
t)  = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
getTagName Tag Text
_             = Maybe Text
forall a. Maybe a
Nothing
isInlineTag :: Tag Text -> Bool
isInlineTag :: Tag Text -> Bool
isInlineTag Tag Text
t = Tag Text -> Bool
isCommentTag Tag Text
t Bool -> Bool -> Bool
|| case Tag Text
t of
  TagOpen Text
"script" [Attribute Text]
_ -> Text
"math/tex" Text -> Text -> Bool
`T.isPrefixOf` Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"type" Tag Text
t
  TagClose Text
"script"  -> Bool
True
  TagOpen Text
name [Attribute Text]
_     -> Text -> Bool
isInlineTagName Text
name
  TagClose Text
name      -> Text -> Bool
isInlineTagName Text
name
  Tag Text
_                  -> Bool
False
 where isInlineTagName :: Text -> Bool
isInlineTagName Text
x =
         Text
x Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.notMember` Set Text
blockTags Bool -> Bool -> Bool
||
         Int -> Text -> Text
T.take Int
1 Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"?" 
isBlockTag :: Tag Text -> Bool
isBlockTag :: Tag Text -> Bool
isBlockTag Tag Text
t = Bool
isBlockTagName Bool -> Bool -> Bool
|| Tag Text -> Bool
forall str. Tag str -> Bool
isTagComment Tag Text
t
                 where isBlockTagName :: Bool
isBlockTagName =
                         case Tag Text -> Maybe Text
getTagName Tag Text
t of
                              Just Text
x
                                | Text
"?" Text -> Text -> Bool
`T.isPrefixOf` Text
x -> Bool
True
                                | Text
"!" Text -> Text -> Bool
`T.isPrefixOf` Text
x -> Bool
True
                                | Bool
otherwise -> Text
x Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
blockTags
                                    Bool -> Bool -> Bool
|| Text
x Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
eitherBlockOrInline
                              Maybe Text
Nothing -> Bool
False
isTextTag :: Tag Text -> Bool
isTextTag :: Tag Text -> Bool
isTextTag = (Text -> Bool) -> Tag Text -> Bool
forall str. (str -> Bool) -> Tag str -> Bool
tagText (Bool -> Text -> Bool
forall a b. a -> b -> a
const Bool
True)
isCommentTag :: Tag Text -> Bool
 = (Text -> Bool) -> Tag Text -> Bool
forall str. (str -> Bool) -> Tag str -> Bool
tagComment (Bool -> Text -> Bool
forall a b. a -> b -> a
const Bool
True)
htmlInBalanced :: Monad m
               => (Tag Text -> Bool)
               -> ParsecT Sources st m Text
htmlInBalanced :: forall (m :: * -> *) st.
Monad m =>
(Tag Text -> Bool) -> ParsecT Sources st m Text
htmlInBalanced Tag Text -> Bool
f = ParsecT Sources st m Text -> ParsecT Sources st m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources st m Text -> ParsecT Sources st m Text)
-> ParsecT Sources st m Text -> ParsecT Sources st m Text
forall a b. (a -> b) -> a -> b
$ do
  ParsecT Sources st m Char -> ParsecT Sources st m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (Char -> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<')
  Sources
sources <- ParsecT Sources st m Sources
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
  let ts :: [Tag Text]
ts = [Tag Text] -> [Tag Text]
forall str. StringLike str => [Tag str] -> [Tag str]
canonicalizeTags
        ([Tag Text] -> [Tag Text]) -> [Tag Text] -> [Tag Text]
forall a b. (a -> b) -> a -> b
$ ParseOptions Text -> Text -> [Tag Text]
forall str. StringLike str => ParseOptions str -> str -> [Tag str]
parseTagsOptions ParseOptions Text
forall str. StringLike str => ParseOptions str
parseOptions{ optTagWarning = True,
                                         optTagPosition = True }
        (Text -> [Tag Text]) -> Text -> [Tag Text]
forall a b. (a -> b) -> a -> b
$ Sources -> Text
sourcesToText Sources
sources
  case [Tag Text]
ts of
    (TagPosition Int
sr Int
sc : t :: Tag Text
t@(TagOpen Text
tn [Attribute Text]
_) : [Tag Text]
rest) -> do
       Bool -> ParsecT Sources st m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources st m ())
-> Bool -> ParsecT Sources st m ()
forall a b. (a -> b) -> a -> b
$ Tag Text -> Bool
f Tag Text
t
       Bool -> ParsecT Sources st m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources st m ())
-> Bool -> ParsecT Sources st m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Tag Text] -> Bool
hasTagWarning (Tag Text
t Tag Text -> [Tag Text] -> [Tag Text]
forall a. a -> [a] -> [a]
: Int -> [Tag Text] -> [Tag Text]
forall a. Int -> [a] -> [a]
take Int
1 [Tag Text]
rest)
       case Text -> [Tag Text] -> [Tag Text]
htmlInBalanced' Text
tn (Tag Text
tTag Text -> [Tag Text] -> [Tag Text]
forall a. a -> [a] -> [a]
:[Tag Text]
rest) of
            []  -> ParsecT Sources st m Text
forall a. ParsecT Sources st m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
            [Tag Text]
xs  -> case [Tag Text] -> [Tag Text]
forall a. [a] -> [a]
reverse [Tag Text]
xs of
                        (TagClose Text
_ : TagPosition Int
er Int
ec : [Tag Text]
_) -> do
                          let ls :: Int
ls = Int
er Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sr
                          let cs :: Int
cs = Int
ec Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sc
                          Text
lscontents <- [Text] -> Text
T.unlines ([Text] -> Text)
-> ParsecT Sources st m [Text] -> ParsecT Sources st m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ParsecT Sources st m Text -> ParsecT Sources st m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
ls ParsecT Sources st m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
                          String
cscontents <- Int -> ParsecT Sources st m Char -> ParsecT Sources st m String
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
cs ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
                          String
closetag <- do
                            String
x <- ParsecT Sources st m Char -> ParsecT Sources st m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ((Char -> Bool) -> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'>'))
                            Char -> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>'
                            String -> ParsecT Sources st m String
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
x String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
">")
                          Text -> ParsecT Sources st m Text
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources st m Text)
-> Text -> ParsecT Sources st m Text
forall a b. (a -> b) -> a -> b
$ Text
lscontents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
cscontents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
closetag
                        [Tag Text]
_ -> ParsecT Sources st m Text
forall a. ParsecT Sources st m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
    [Tag Text]
_ -> ParsecT Sources st m Text
forall a. ParsecT Sources st m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
htmlInBalanced' :: Text
                -> [Tag Text]
                -> [Tag Text]
htmlInBalanced' :: Text -> [Tag Text] -> [Tag Text]
htmlInBalanced' Text
tagname [Tag Text]
ts = [Tag Text] -> Maybe [Tag Text] -> [Tag Text]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [Tag Text] -> [Tag Text]) -> Maybe [Tag Text] -> [Tag Text]
forall a b. (a -> b) -> a -> b
$ Int -> [Tag Text] -> Maybe [Tag Text]
go Int
0 [Tag Text]
ts
  where go :: Int -> [Tag Text] -> Maybe [Tag Text]
        go :: Int -> [Tag Text] -> Maybe [Tag Text]
go Int
n (t :: Tag Text
t@(TagOpen Text
tn' [Attribute Text]
_):[Tag Text]
rest) | Text
tn' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
tagname =
              (Tag Text
t Tag Text -> [Tag Text] -> [Tag Text]
forall a. a -> [a] -> [a]
:) ([Tag Text] -> [Tag Text]) -> Maybe [Tag Text] -> Maybe [Tag Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> [Tag Text] -> Maybe [Tag Text]
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) [Tag Text]
rest
        go Int
1 (t :: Tag Text
t@(TagClose Text
tn'):[Tag Text]
_) | Text
tn' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
tagname =
              [Tag Text] -> Maybe [Tag Text]
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return [Tag Text
t]
        go Int
n (t :: Tag Text
t@(TagClose Text
tn'):[Tag Text]
rest)  | Text
tn' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
tagname =
              (Tag Text
t Tag Text -> [Tag Text] -> [Tag Text]
forall a. a -> [a] -> [a]
:) ([Tag Text] -> [Tag Text]) -> Maybe [Tag Text] -> Maybe [Tag Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> [Tag Text] -> Maybe [Tag Text]
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [Tag Text]
rest
        go Int
n (Tag Text
t:[Tag Text]
ts') = (Tag Text
t Tag Text -> [Tag Text] -> [Tag Text]
forall a. a -> [a] -> [a]
:) ([Tag Text] -> [Tag Text]) -> Maybe [Tag Text] -> Maybe [Tag Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> [Tag Text] -> Maybe [Tag Text]
go Int
n [Tag Text]
ts'
        go Int
_ [] = Maybe [Tag Text]
forall a. Maybe a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
hasTagWarning :: [Tag Text] -> Bool
hasTagWarning :: [Tag Text] -> Bool
hasTagWarning (TagWarning Text
_:[Tag Text]
_) = Bool
True
hasTagWarning [Tag Text]
_                = Bool
False
htmlTag :: (HasReaderOptions st, Monad m)
        => (Tag Text -> Bool)
        -> ParsecT Sources st m (Tag Text, Text)
htmlTag :: forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
f = ParsecT Sources st m (Tag Text, Text)
-> ParsecT Sources st m (Tag Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources st m (Tag Text, Text)
 -> ParsecT Sources st m (Tag Text, Text))
-> ParsecT Sources st m (Tag Text, Text)
-> ParsecT Sources st m (Tag Text, Text)
forall a b. (a -> b) -> a -> b
$ do
  ParsecT Sources st m Char -> ParsecT Sources st m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (Char -> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<')
  SourcePos
startpos <- ParsecT Sources st m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  Sources
sources <- ParsecT Sources st m Sources
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
  let inp :: Text
inp = Sources -> Text
sourcesToText Sources
sources
  let ts :: [Tag Text]
ts = [Tag Text] -> [Tag Text]
forall str. StringLike str => [Tag str] -> [Tag str]
canonicalizeTags ([Tag Text] -> [Tag Text]) -> [Tag Text] -> [Tag Text]
forall a b. (a -> b) -> a -> b
$ ParseOptions Text -> Text -> [Tag Text]
forall str. StringLike str => ParseOptions str -> str -> [Tag str]
parseTagsOptions
                               ParseOptions Text
forall str. StringLike str => ParseOptions str
parseOptions{ optTagWarning = False
                                           , optTagPosition = True }
                               (Text
inp Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ")
                               
                               
  (Tag Text
next, Int
ln, Int
col) <- case [Tag Text]
ts of
                      (TagPosition{} : Tag Text
next : TagPosition Int
ln Int
col : [Tag Text]
_)
                        | Tag Text -> Bool
f Tag Text
next -> (Tag Text, Int, Int) -> ParsecT Sources st m (Tag Text, Int, Int)
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Tag Text
next, Int
ln, Int
col)
                      [Tag Text]
_ -> ParsecT Sources st m (Tag Text, Int, Int)
forall a. ParsecT Sources st m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  
  
  
  
  let isNameChar :: Char -> Bool
isNameChar Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'
  let isName :: Text -> Bool
isName Text
s = case Text -> Maybe (Char, Text)
T.uncons Text
s of
                   Maybe (Char, Text)
Nothing      -> Bool
False
                   Just (Char
c, Text
cs) -> Char -> Bool
isLetter Char
c Bool -> Bool -> Bool
&& (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isNameChar Text
cs
  let isPI :: Text -> Bool
isPI Text
s = case Text -> Maybe (Char, Text)
T.uncons Text
s of
                 Just (Char
'?', Text
_) -> Bool
True 
                 Maybe (Char, Text)
_             -> Bool
False
  let endpos :: SourcePos
endpos = if Int
ln Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
                  then SourcePos -> Int -> SourcePos
setSourceColumn SourcePos
startpos
                         (SourcePos -> Int
sourceColumn SourcePos
startpos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
col Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1))
                  else SourcePos -> Int -> SourcePos
setSourceColumn (SourcePos -> Int -> SourcePos
setSourceLine SourcePos
startpos
                                        (SourcePos -> Int
sourceLine SourcePos
startpos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
ln Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)))
                         Int
col
  let endAngle :: ParsecT Sources u m ()
endAngle = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$
        do Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>'
           SourcePos
pos <- ParsecT Sources u m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
           Bool -> ParsecT Sources u m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources u m ()) -> Bool -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ SourcePos
pos SourcePos -> SourcePos -> Bool
forall a. Ord a => a -> a -> Bool
>= SourcePos
endpos
  let handleTag :: Text -> ParsecT Sources u m (Tag Text, Text)
handleTag Text
tagname = do
       
       
       Bool -> ParsecT Sources u m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources u m ()) -> Bool -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ Text -> Bool
isName Text
tagname Bool -> Bool -> Bool
|| Text -> Bool
isPI Text
tagname
       Bool -> ParsecT Sources u m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources u m ()) -> Bool -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Bool
T.null Text
tagname
       
       
       Bool -> ParsecT Sources u m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources u m ()) -> Bool -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ HasCallStack => Text -> Char
Text -> Char
T.last Text
tagname Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
':'
       Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<'
       String
rendered <- ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar ParsecT Sources u m ()
forall {u}. ParsecT Sources u m ()
endAngle
       (Tag Text, Text) -> ParsecT Sources u m (Tag Text, Text)
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Tag Text
next, String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"<" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
rendered String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
">")
  case Tag Text
next of
       TagComment Text
s
         | Text
"<!--" Text -> Text -> Bool
`T.isPrefixOf` Text
inp -> do
          String -> ParsecT Sources st m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"<!--"
          Int -> ParsecT Sources st m Char -> ParsecT Sources st m String
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count (Text -> Int
T.length Text
s) ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
          String -> ParsecT Sources st m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"-->"
          Bool
stripComments <- (ReaderOptions -> Bool) -> ParsecT Sources st m Bool
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
forall s (m :: * -> *) t b.
Stream s m t =>
(ReaderOptions -> b) -> ParsecT s st m b
getOption ReaderOptions -> Bool
readerStripComments
          if Bool
stripComments
             then (Tag Text, Text) -> ParsecT Sources st m (Tag Text, Text)
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Tag Text
next, Text
"")
             else (Tag Text, Text) -> ParsecT Sources st m (Tag Text, Text)
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Tag Text
next, Text
"<!--" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-->")
         | Bool
otherwise -> String -> ParsecT Sources st m (Tag Text, Text)
forall a. String -> ParsecT Sources st m a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail String
"bogus comment mode, HTML5 parse error"
       TagOpen Text
tagname [Attribute Text]
attr -> do
         Bool -> ParsecT Sources st m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources st m ())
-> Bool -> ParsecT Sources st m ()
forall a b. (a -> b) -> a -> b
$ Text -> Bool
isPI Text
tagname Bool -> Bool -> Bool
|| (Attribute Text -> Bool) -> [Attribute Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Text -> Bool
isName (Text -> Bool)
-> (Attribute Text -> Text) -> Attribute Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attribute Text -> Text
forall a b. (a, b) -> a
fst) [Attribute Text]
attr
         Text -> ParsecT Sources st m (Tag Text, Text)
forall {u}. Text -> ParsecT Sources u m (Tag Text, Text)
handleTag Text
tagname
       TagClose Text
tagname ->
         Text -> ParsecT Sources st m (Tag Text, Text)
forall {u}. Text -> ParsecT Sources u m (Tag Text, Text)
handleTag Text
tagname
       Tag Text
_ -> ParsecT Sources st m (Tag Text, Text)
forall a. ParsecT Sources st m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
canonicalizeUrl :: PandocMonad m => Text -> TagParser m Text
canonicalizeUrl :: forall (m :: * -> *). PandocMonad m => Text -> TagParser m Text
canonicalizeUrl Text
url = do
  Maybe URI
mbBaseHref <- HTMLState -> Maybe URI
baseHref (HTMLState -> Maybe URI)
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
-> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) (Maybe URI)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) HTMLState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Text -> TagParser m Text
forall a. a -> ParsecT [Tag Text] HTMLState (ReaderT HTMLLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> TagParser m Text) -> Text -> TagParser m Text
forall a b. (a -> b) -> a -> b
$ case (String -> Maybe URI
parseURIReference (Text -> String
T.unpack Text
url), Maybe URI
mbBaseHref) of
                (Just URI
rel, Just URI
bs) -> URI -> Text
forall a. Show a => a -> Text
tshow (URI
rel URI -> URI -> URI
`nonStrictRelativeTo` URI
bs)
                (Maybe URI, Maybe URI)
_                   -> Text
url