{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Text.Pandoc.Readers.Markdown (
readMarkdown,
yamlToMeta,
yamlToRefs ) where
import Control.Monad
import Control.Monad.Except (throwError)
import Data.Bifunctor (second)
import Data.Char (isAlphaNum, isPunctuation, isSpace)
import Data.List (transpose, elemIndex, sortOn, foldl')
import qualified Data.Map as M
import Data.Maybe
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.ByteString as BS
import System.FilePath (addExtension, takeExtension, takeDirectory)
import qualified System.FilePath.Windows as Windows
import qualified System.FilePath.Posix as Posix
import Text.DocLayout (realLength)
import Text.HTML.TagSoup hiding (Row)
import Text.Pandoc.Builder (Blocks, Inlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..), report)
import Text.Pandoc.Definition as Pandoc
import Text.Pandoc.Emoji (emojiToInline)
import Text.Pandoc.Error
import Safe.Foldable (maximumBounded)
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Walk (walk)
import Text.Pandoc.Parsing hiding (tableCaption)
import Text.Pandoc.Readers.HTML (htmlInBalanced, htmlTag, isBlockTag,
isCommentTag, isInlineTag, isTextTag)
import Text.Pandoc.Readers.LaTeX (applyMacros, rawLaTeXBlock, rawLaTeXInline)
import Text.Pandoc.Shared
import Text.Pandoc.URI (escapeURI, isURI)
import Text.Pandoc.XML (fromEntities)
import Text.Pandoc.Readers.Metadata (yamlBsToMeta, yamlBsToRefs, yamlMetaBlock)
type MarkdownParser m = ParsecT Sources ParserState m
type F = Future ParserState
readMarkdown :: (PandocMonad m, ToSources a)
=> ReaderOptions
-> a
-> m Pandoc
readMarkdown :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readMarkdown ReaderOptions
opts a
s = do
Either PandocError Pandoc
parsed <- ParsecT Sources ParserState m Pandoc
-> ParserState -> Sources -> m (Either PandocError Pandoc)
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParsecT Sources ParserState m Pandoc
forall (m :: * -> *). PandocMonad m => MarkdownParser m Pandoc
parseMarkdown ParserState
forall a. Default a => a
def{ stateOptions = opts }
(Int -> Sources -> Sources
ensureFinalNewlines Int
3 (a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s))
case Either PandocError Pandoc
parsed of
Right Pandoc
result -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
result
Left PandocError
e -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
yamlToMeta :: PandocMonad m
=> ReaderOptions
-> Maybe FilePath
-> BS.ByteString
-> m Meta
yamlToMeta :: forall (m :: * -> *).
PandocMonad m =>
ReaderOptions -> Maybe FilePath -> ByteString -> m Meta
yamlToMeta ReaderOptions
opts Maybe FilePath
mbfp ByteString
bstr = do
let parser :: ParsecT Sources ParserState m Meta
parser = do
SourcePos
oldPos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
SourcePos -> ParsecT Sources ParserState m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition (SourcePos -> ParsecT Sources ParserState m ())
-> SourcePos -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> SourcePos
initialPos (FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
"" Maybe FilePath
mbfp)
Future ParserState Meta
meta <- ParsecT Sources ParserState m (Future ParserState MetaValue)
-> ByteString
-> ParsecT Sources ParserState m (Future ParserState Meta)
forall (m :: * -> *) st.
(PandocMonad m, HasLastStrPosition st) =>
ParsecT Sources st m (Future st MetaValue)
-> ByteString -> ParsecT Sources st m (Future st Meta)
yamlBsToMeta ((Blocks -> MetaValue)
-> Future ParserState Blocks -> Future ParserState MetaValue
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Blocks -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
B.toMetaValue (Future ParserState Blocks -> Future ParserState MetaValue)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState MetaValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks) ByteString
bstr
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
checkNotes
SourcePos -> ParsecT Sources ParserState m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
oldPos
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let result :: Meta
result = Future ParserState Meta -> ParserState -> Meta
forall s a. Future s a -> s -> a
runF Future ParserState Meta
meta ParserState
st
ParsecT Sources ParserState m ()
forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParsecT s st m ()
reportLogMessages
Meta -> ParsecT Sources ParserState m Meta
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Meta
result
Either PandocError Meta
parsed <- ParsecT Sources ParserState m Meta
-> ParserState -> Text -> m (Either PandocError Meta)
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParsecT Sources ParserState m Meta
parser ParserState
forall a. Default a => a
def{ stateOptions = opts } (Text
"" :: Text)
case Either PandocError Meta
parsed of
Right Meta
result -> Meta -> m Meta
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Meta
result
Left PandocError
e -> PandocError -> m Meta
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
yamlToRefs :: PandocMonad m
=> (Text -> Bool)
-> ReaderOptions
-> Maybe FilePath
-> BS.ByteString
-> m [MetaValue]
yamlToRefs :: forall (m :: * -> *).
PandocMonad m =>
(Text -> Bool)
-> ReaderOptions -> Maybe FilePath -> ByteString -> m [MetaValue]
yamlToRefs Text -> Bool
idpred ReaderOptions
opts Maybe FilePath
mbfp ByteString
bstr = do
let parser :: ParsecT Sources ParserState m [MetaValue]
parser = do
case Maybe FilePath
mbfp of
Maybe FilePath
Nothing -> () -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just FilePath
fp -> SourcePos -> ParsecT Sources ParserState m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition (SourcePos -> ParsecT Sources ParserState m ())
-> SourcePos -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> SourcePos
initialPos FilePath
fp
Future ParserState [MetaValue]
refs <- ParsecT Sources ParserState m (Future ParserState MetaValue)
-> (Text -> Bool)
-> ByteString
-> ParsecT Sources ParserState m (Future ParserState [MetaValue])
forall (m :: * -> *) st.
(PandocMonad m, HasLastStrPosition st) =>
ParsecT Sources st m (Future st MetaValue)
-> (Text -> Bool)
-> ByteString
-> ParsecT Sources st m (Future st [MetaValue])
yamlBsToRefs ((Blocks -> MetaValue)
-> Future ParserState Blocks -> Future ParserState MetaValue
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Blocks -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
B.toMetaValue (Future ParserState Blocks -> Future ParserState MetaValue)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState MetaValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks) Text -> Bool
idpred ByteString
bstr
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
checkNotes
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let result :: [MetaValue]
result = Future ParserState [MetaValue] -> ParserState -> [MetaValue]
forall s a. Future s a -> s -> a
runF Future ParserState [MetaValue]
refs ParserState
st
ParsecT Sources ParserState m ()
forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParsecT s st m ()
reportLogMessages
[MetaValue] -> ParsecT Sources ParserState m [MetaValue]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return [MetaValue]
result
Either PandocError [MetaValue]
parsed <- ParsecT Sources ParserState m [MetaValue]
-> ParserState -> Text -> m (Either PandocError [MetaValue])
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParsecT Sources ParserState m [MetaValue]
parser ParserState
forall a. Default a => a
def{ stateOptions = opts } (Text
"" :: Text)
case Either PandocError [MetaValue]
parsed of
Right [MetaValue]
result -> [MetaValue] -> m [MetaValue]
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return [MetaValue]
result
Left PandocError
e -> PandocError -> m [MetaValue]
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
isBulletListMarker :: Char -> Bool
isBulletListMarker :: Char -> Bool
isBulletListMarker Char
'*' = Bool
True
isBulletListMarker Char
'+' = Bool
True
isBulletListMarker Char
'-' = Bool
True
isBulletListMarker Char
_ = Bool
False
isHruleChar :: Char -> Bool
isHruleChar :: Char -> Bool
isHruleChar Char
'*' = Bool
True
isHruleChar Char
'-' = Bool
True
isHruleChar Char
'_' = Bool
True
isHruleChar Char
_ = Bool
False
setextHChars :: [Char]
setextHChars :: FilePath
setextHChars = FilePath
"=-"
inList :: PandocMonad m => MarkdownParser m ()
inList :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
inList = do
ParserContext
ctx <- ParserState -> ParserContext
stateParserContext (ParserState -> ParserContext)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m ParserContext
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> MarkdownParser m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (ParserContext
ctx ParserContext -> ParserContext -> Bool
forall a. Eq a => a -> a -> Bool
== ParserContext
ListItemState)
spnl :: PandocMonad m => ParsecT Sources st m ()
spnl :: forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl = ParsecT Sources st m () -> ParsecT Sources st m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources st m () -> ParsecT Sources st m ())
-> ParsecT Sources st m () -> ParsecT Sources st m ()
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources st m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
ParsecT Sources st m Char -> ParsecT Sources st m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
ParsecT Sources st m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
ParsecT Sources st m Char -> ParsecT Sources st m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (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
'\n')
spnl' :: PandocMonad m => ParsecT Sources st m Text
spnl' :: forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Text
spnl' = 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
FilePath
xs <- ParsecT Sources st m Char -> ParsecT Sources st m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
FilePath
ys <- FilePath
-> ParsecT Sources st m FilePath -> ParsecT Sources st m FilePath
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option FilePath
"" (ParsecT Sources st m FilePath -> ParsecT Sources st m FilePath)
-> ParsecT Sources st m FilePath -> ParsecT Sources st m FilePath
forall a b. (a -> b) -> a -> b
$ ParsecT Sources st m FilePath -> ParsecT Sources st m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources st m FilePath -> ParsecT Sources st m FilePath)
-> ParsecT Sources st m FilePath -> ParsecT Sources st m FilePath
forall a b. (a -> b) -> a -> b
$ (:) (Char -> FilePath -> FilePath)
-> ParsecT Sources st m Char
-> ParsecT Sources st m (FilePath -> FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
ParsecT Sources st m (FilePath -> FilePath)
-> ParsecT Sources st m FilePath -> ParsecT Sources st m FilePath
forall a b.
ParsecT Sources st m (a -> b)
-> ParsecT Sources st m a -> ParsecT Sources st m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ParsecT Sources st m Char -> ParsecT Sources st m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources st m FilePath
-> ParsecT Sources st m () -> ParsecT Sources st m FilePath
forall a b.
ParsecT Sources st m a
-> ParsecT Sources st m b -> ParsecT Sources st m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources st m Char -> ParsecT Sources st m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (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
'\n'))
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
$ FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath
xs FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
ys
indentSpaces :: PandocMonad m => MarkdownParser m Text
indentSpaces :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentSpaces = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
Int
tabStop <- (ReaderOptions -> Int) -> ParsecT Sources ParserState m Int
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 ParserState m b
getOption ReaderOptions -> Int
readerTabStop
Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
tabStop (Char -> ParsecT Sources ParserState 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 ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
"\t" ParsecT Sources ParserState m Text
-> FilePath -> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> FilePath -> ParsecT s u m a
<?> FilePath
"indentation"
nonindentSpaces :: PandocMonad m => MarkdownParser m Text
nonindentSpaces :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
nonindentSpaces = do
Int
n <- MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces
Text -> MarkdownParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> MarkdownParser m Text) -> Text -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.replicate Int
n Text
" "
skipNonindentSpaces :: PandocMonad m => MarkdownParser m Int
skipNonindentSpaces :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces = do
Int
tabStop <- (ReaderOptions -> Int) -> MarkdownParser m Int
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 ParserState m b
getOption ReaderOptions -> Int
readerTabStop
Int -> MarkdownParser m Int
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m Int
gobbleAtMostSpaces (Int
tabStop Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) MarkdownParser m Int
-> ParsecT Sources ParserState m () -> MarkdownParser m Int
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
litChar :: PandocMonad m => MarkdownParser m Text
litChar :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar = Char -> Text
T.singleton (Char -> Text)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
escapedChar'
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
characterReference
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> Text
T.singleton (Char -> Text)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
noneOf FilePath
"\n"
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
" ")
inBalancedBrackets :: PandocMonad m
=> MarkdownParser m (F a)
-> MarkdownParser m (F a)
inBalancedBrackets :: forall (m :: * -> *) a.
PandocMonad m =>
MarkdownParser m (F a) -> MarkdownParser m (F a)
inBalancedBrackets MarkdownParser m (F a)
innerParser =
MarkdownParser m (F a) -> MarkdownParser m (F a)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F a) -> MarkdownParser m (F a))
-> MarkdownParser m (F a) -> MarkdownParser m (F a)
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ((), Text)
-> ParsecT Sources ParserState m ((), Text)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ((), Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw (Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m ()
go Int
1) ParsecT Sources ParserState m ((), Text)
-> (((), Text) -> MarkdownParser m (F a)) -> MarkdownParser m (F a)
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
MarkdownParser m (F a) -> Text -> MarkdownParser m (F a)
forall (m :: * -> *) st r.
Monad m =>
ParsecT Sources st m r -> Text -> ParsecT Sources st m r
parseFromString MarkdownParser m (F a)
innerParser (Text -> MarkdownParser m (F a))
-> (((), Text) -> Text) -> ((), Text) -> MarkdownParser m (F a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
stripBracket (Text -> Text) -> (((), Text) -> Text) -> ((), Text) -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((), Text) -> Text
forall a b. (a, b) -> b
snd
where stripBracket :: Text -> Text
stripBracket Text
t = case Text -> Maybe (Text, Char)
T.unsnoc Text
t of
Just (Text
t', Char
']') -> Text
t'
Maybe (Text, Char)
_ -> Text
t
go :: PandocMonad m => Int -> MarkdownParser m ()
go :: forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m ()
go Int
0 = () -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
go Int
openBrackets =
(() ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
escapedChar ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
code ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
math ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
endline ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
rawHtmlInline ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
rawLaTeXInline') ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m ()
go Int
openBrackets)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(do Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']'
Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
Control.Monad.when (Int
openBrackets Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1) (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m ()
go (Int
openBrackets Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1))
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m ()
go (Int
openBrackets Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
((Char -> Bool) -> ParsecT Sources ParserState 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
'\n') ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m ()
go Int
openBrackets)
rawTitleBlockLine :: PandocMonad m => MarkdownParser m Text
rawTitleBlockLine :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawTitleBlockLine = do
Char -> ParsecT Sources ParserState 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 ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Text
first <- MarkdownParser m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
[Text]
rest <- MarkdownParser m Text -> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MarkdownParser m Text -> ParsecT Sources ParserState m [Text])
-> MarkdownParser m Text -> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m Text -> MarkdownParser m Text)
-> MarkdownParser m Text -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ do ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
MarkdownParser m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
Text -> MarkdownParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> MarkdownParser m Text) -> Text -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
trim (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines (Text
firstText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
rest)
titleLine :: PandocMonad m => MarkdownParser m (F Inlines)
titleLine :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
titleLine = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Text
raw <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawTitleBlockLine
F Inlines
res <- ParsecT Sources ParserState m (F Inlines)
-> Text -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines Text
raw
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> ParsecT Sources ParserState m (F Inlines))
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF F Inlines
res
authorsLine :: PandocMonad m => MarkdownParser m (F [Inlines])
authorsLine :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Inlines])
authorsLine = ParsecT Sources ParserState m (F [Inlines])
-> ParsecT Sources ParserState m (F [Inlines])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F [Inlines])
-> ParsecT Sources ParserState m (F [Inlines]))
-> ParsecT Sources ParserState m (F [Inlines])
-> ParsecT Sources ParserState m (F [Inlines])
forall a b. (a -> b) -> a -> b
$ do
Text
raw <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawTitleBlockLine
let sep :: ParsecT Sources u m Char
sep = (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
';' ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources u m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces) ParsecT Sources u m Char
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
let pAuthors :: ParsecT Sources ParserState m [F Inlines]
pAuthors = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [F Inlines]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepEndBy
(F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many
(ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
sep ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline))
ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
sep
[F Inlines] -> F [Inlines]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([F Inlines] -> F [Inlines])
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m (F [Inlines])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m [F Inlines]
-> Text -> ParsecT Sources ParserState m [F Inlines]
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m [F Inlines]
pAuthors Text
raw
dateLine :: PandocMonad m => MarkdownParser m (F Inlines)
dateLine :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
dateLine = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Text
raw <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawTitleBlockLine
F Inlines
res <- ParsecT Sources ParserState m (F Inlines)
-> Text -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines Text
raw
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> ParsecT Sources ParserState m (F Inlines))
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF F Inlines
res
titleBlock :: PandocMonad m => MarkdownParser m ()
titleBlock :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
titleBlock = MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
pandocTitleBlock MarkdownParser m () -> MarkdownParser m () -> MarkdownParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
mmdTitleBlock
pandocTitleBlock :: PandocMonad m => MarkdownParser m ()
pandocTitleBlock :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
pandocTitleBlock = do
Extension -> MarkdownParser m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_pandoc_title_block
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState 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 ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'%')
MarkdownParser m () -> MarkdownParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m () -> MarkdownParser m ())
-> MarkdownParser m () -> MarkdownParser m ()
forall a b. (a -> b) -> a -> b
$ do
F Inlines
title <- F Inlines
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option F Inlines
forall a. Monoid a => a
mempty ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
titleLine
F [Inlines]
author <- F [Inlines]
-> ParsecT Sources ParserState m (F [Inlines])
-> ParsecT Sources ParserState m (F [Inlines])
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option ([Inlines] -> F [Inlines]
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return []) ParsecT Sources ParserState m (F [Inlines])
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Inlines])
authorsLine
F Inlines
date <- F Inlines
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option F Inlines
forall a. Monoid a => a
mempty ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
dateLine
ParsecT Sources ParserState m Text -> MarkdownParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
let meta' :: Future ParserState Meta
meta' = do Inlines
title' <- F Inlines
title
[Inlines]
author' <- F [Inlines]
author
Inlines
date' <- F Inlines
date
Meta -> Future ParserState Meta
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Meta -> Future ParserState Meta)
-> Meta -> Future ParserState Meta
forall a b. (a -> b) -> a -> b
$
(if Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
title'
then Meta -> Meta
forall a. a -> a
id
else Text -> Inlines -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
B.setMeta Text
"title" Inlines
title')
(Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if [Inlines] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inlines]
author'
then Meta -> Meta
forall a. a -> a
id
else Text -> [Inlines] -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
B.setMeta Text
"author" [Inlines]
author')
(Meta -> Meta) -> (Meta -> Meta) -> Meta -> Meta
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
date'
then Meta -> Meta
forall a. a -> a
id
else Text -> Inlines -> Meta -> Meta
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Meta -> Meta
B.setMeta Text
"date" Inlines
date')
(Meta -> Meta) -> Meta -> Meta
forall a b. (a -> b) -> a -> b
$ Meta
nullMeta
(ParserState -> ParserState) -> MarkdownParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> MarkdownParser m ())
-> (ParserState -> ParserState) -> MarkdownParser m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateMeta' = stateMeta' st <> meta' }
yamlMetaBlock' :: PandocMonad m => MarkdownParser m (F Blocks)
yamlMetaBlock' :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
yamlMetaBlock' = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_yaml_metadata_block
Future ParserState Meta
newMetaF <- ParsecT Sources ParserState m (Future ParserState MetaValue)
-> ParsecT Sources ParserState m (Future ParserState Meta)
forall st (m :: * -> *).
(HasLastStrPosition st, PandocMonad m) =>
ParsecT Sources st m (Future st MetaValue)
-> ParsecT Sources st m (Future st Meta)
yamlMetaBlock ((Blocks -> MetaValue)
-> Future ParserState Blocks -> Future ParserState MetaValue
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Blocks -> MetaValue
forall a. ToMetaValue a => a -> MetaValue
B.toMetaValue (Future ParserState Blocks -> Future ParserState MetaValue)
-> MarkdownParser m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState MetaValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks)
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateMeta' = stateMeta' st <> newMetaF }
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Future ParserState Blocks
forall a. Monoid a => a
mempty
mmdTitleBlock :: PandocMonad m => MarkdownParser m ()
mmdTitleBlock :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
mmdTitleBlock = do
Extension -> MarkdownParser m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_mmd_title_block
MarkdownParser m () -> MarkdownParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m () -> MarkdownParser m ())
-> MarkdownParser m () -> MarkdownParser m ()
forall a b. (a -> b) -> a -> b
$ do
(Text, MetaValue)
firstPair <- Bool -> MarkdownParser m (Text, MetaValue)
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (Text, MetaValue)
kvPair Bool
False
[(Text, MetaValue)]
restPairs <- MarkdownParser m (Text, MetaValue)
-> ParsecT Sources ParserState m [(Text, MetaValue)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Bool -> MarkdownParser m (Text, MetaValue)
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (Text, MetaValue)
kvPair Bool
True)
let kvPairs :: [(Text, MetaValue)]
kvPairs = (Text, MetaValue)
firstPair (Text, MetaValue) -> [(Text, MetaValue)] -> [(Text, MetaValue)]
forall a. a -> [a] -> [a]
: [(Text, MetaValue)]
restPairs
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
(ParserState -> ParserState) -> MarkdownParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> MarkdownParser m ())
-> (ParserState -> ParserState) -> MarkdownParser m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateMeta' = stateMeta' st <>
return (Meta $ M.fromList kvPairs) }
kvPair :: PandocMonad m => Bool -> MarkdownParser m (Text, MetaValue)
kvPair :: forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (Text, MetaValue)
kvPair Bool
allowEmpty = ParsecT Sources ParserState m (Text, MetaValue)
-> ParsecT Sources ParserState m (Text, MetaValue)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Text, MetaValue)
-> ParsecT Sources ParserState m (Text, MetaValue))
-> ParsecT Sources ParserState m (Text, MetaValue)
-> ParsecT Sources ParserState m (Text, MetaValue)
forall a b. (a -> b) -> a -> b
$ do
Text
key <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar (ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
"_- ") (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':')
Text
val <- Text -> Text
trim (Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
(ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar))
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Bool
allowEmpty Bool -> Bool -> Bool
|| Bool -> Bool
not (Text -> Bool
T.null Text
val)
let key' :: Text
key' = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toLower Text
key
let val' :: MetaValue
val' = [Inline] -> MetaValue
MetaInlines ([Inline] -> MetaValue) -> [Inline] -> MetaValue
forall a b. (a -> b) -> a -> b
$ Inlines -> [Inline]
forall a. Many a -> [a]
B.toList (Inlines -> [Inline]) -> Inlines -> [Inline]
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text Text
val
(Text, MetaValue)
-> ParsecT Sources ParserState m (Text, MetaValue)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
key',MetaValue
val')
parseMarkdown :: PandocMonad m => MarkdownParser m Pandoc
parseMarkdown :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Pandoc
parseMarkdown = do
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
titleBlock
Future ParserState Blocks
blocks <- MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
checkNotes
let doc :: Pandoc
doc = Future ParserState Pandoc -> ParserState -> Pandoc
forall s a. Future s a -> s -> a
runF (do Pandoc Meta
_ [Block]
bs <- Blocks -> Pandoc
B.doc (Blocks -> Pandoc)
-> Future ParserState Blocks -> Future ParserState Pandoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future ParserState Blocks
blocks
Meta
meta <- ParserState -> Future ParserState Meta
stateMeta' ParserState
st
Pandoc -> Future ParserState Pandoc
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> Future ParserState Pandoc)
-> Pandoc -> Future ParserState Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc Meta
meta [Block]
bs) ParserState
st
ParsecT Sources ParserState m ()
forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParsecT s st m ()
reportLogMessages
Pandoc -> MarkdownParser m Pandoc
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
doc
checkNotes :: PandocMonad m => MarkdownParser m ()
checkNotes :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
checkNotes = do
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let notesUsed :: Set Text
notesUsed = ParserState -> Set Text
stateNoteRefs ParserState
st
let notesDefined :: [Text]
notesDefined = Map Text (SourcePos, Future ParserState Blocks) -> [Text]
forall k a. Map k a -> [k]
M.keys (ParserState -> Map Text (SourcePos, Future ParserState Blocks)
stateNotes' ParserState
st)
(Text -> MarkdownParser m ()) -> [Text] -> MarkdownParser m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\Text
n -> Bool -> MarkdownParser m () -> MarkdownParser m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text
n Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
notesUsed) (MarkdownParser m () -> MarkdownParser m ())
-> MarkdownParser m () -> MarkdownParser m ()
forall a b. (a -> b) -> a -> b
$
case Text
-> Map Text (SourcePos, Future ParserState Blocks)
-> Maybe (SourcePos, Future ParserState Blocks)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
n (ParserState -> Map Text (SourcePos, Future ParserState Blocks)
stateNotes' ParserState
st) of
Just (SourcePos
pos, Future ParserState Blocks
_) -> LogMessage -> MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (Text -> SourcePos -> LogMessage
NoteDefinedButNotUsed Text
n SourcePos
pos)
Maybe (SourcePos, Future ParserState Blocks)
Nothing -> PandocError -> MarkdownParser m ()
forall a. PandocError -> ParsecT Sources ParserState m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> MarkdownParser m ())
-> PandocError -> MarkdownParser m ()
forall a b. (a -> b) -> a -> b
$
Text -> PandocError
PandocShouldNeverHappenError Text
"note not found")
[Text]
notesDefined
referenceKey :: PandocMonad m => MarkdownParser m (F Blocks)
referenceKey :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
referenceKey = ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
SourcePos
pos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
cite)
(F Inlines
_,Text
raw) <- MarkdownParser m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference
Char -> ParsecT Sources ParserState 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 ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'[')
let sourceURL :: ParsecT Sources ParserState m Text
sourceURL = ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Text] -> Text
T.unwords (ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
referenceTitle
ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_link_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_mmd_link_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
keyValAttr)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (() ()
-> MarkdownParser m (F Inlines, Text)
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ MarkdownParser m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference)
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
space ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar)
let betweenAngles :: ParsecT Sources ParserState m Text
betweenAngles = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>'))
Bool
rebase <- Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (Bool
True Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_rebase_relative_paths)
Text
src <- (if Bool
rebase then SourcePos -> Text -> Text
rebasePath SourcePos
pos else Text -> Text
forall a. a -> a
id) (Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Text
betweenAngles ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
sourceURL)
Text
tit <- Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
referenceTitle
Attr
attr <- Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState 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 Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$
do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_link_attributes
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes
[Attr -> Attr]
addKvs <- [Attr -> Attr]
-> ParsecT Sources ParserState m [Attr -> Attr]
-> ParsecT Sources ParserState m [Attr -> Attr]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] (ParsecT Sources ParserState m [Attr -> Attr]
-> ParsecT Sources ParserState m [Attr -> Attr])
-> ParsecT Sources ParserState m [Attr -> Attr]
-> ParsecT Sources ParserState m [Attr -> Attr]
forall a b. (a -> b) -> a -> b
$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_mmd_link_attributes
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Attr -> Attr]
-> ParsecT Sources ParserState m [Attr -> Attr]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m [Attr -> Attr]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr))
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
keyValAttr)
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
let attr' :: Attr
attr' = Attr -> Attr
extractIdClass (Attr -> Attr) -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ (Attr -> (Attr -> Attr) -> Attr) -> Attr -> [Attr -> Attr] -> Attr
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Attr
x Attr -> Attr
f -> Attr -> Attr
f Attr
x) Attr
attr [Attr -> Attr]
addKvs
target :: Target
target = (Text -> Text
escapeURI (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
trimr Text
src, Text
tit)
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let oldkeys :: KeyTable
oldkeys = ParserState -> KeyTable
stateKeys ParserState
st
let key :: Key
key = Text -> Key
toKey Text
raw
case Key -> KeyTable -> Maybe (Target, Attr)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Key
key KeyTable
oldkeys of
Just (Target
t,Attr
a) | Bool -> Bool
not (Target
t Target -> Target -> Bool
forall a. Eq a => a -> a -> Bool
== Target
target Bool -> Bool -> Bool
&& Attr
a Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
attr') ->
LogMessage -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage -> ParsecT Sources ParserState m ())
-> LogMessage -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
DuplicateLinkReference Text
raw SourcePos
pos
Maybe (Target, Attr)
_ -> () -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
s -> ParserState
s { stateKeys = M.insert key (target, attr') oldkeys }
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
referenceTitle :: PandocMonad m => MarkdownParser m Text
referenceTitle :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
referenceTitle = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Char -> ParsecT Sources ParserState m Text
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
quotedTitle Char
'"' ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT Sources ParserState m Text
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
quotedTitle Char
'\'' ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char
-> Char
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
Char -> Char -> ParsecT s st m Text -> ParsecT s st m Text
charsInBalanced Char
'(' Char
')' ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar
quotedTitle :: PandocMonad m => Char -> MarkdownParser m Text
quotedTitle :: forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
quotedTitle Char
c = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
let pEnder :: ParsecT Sources u m ()
pEnder = 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
$ 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
c ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ((Char -> Bool) -> ParsecT Sources u 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
isAlphaNum)
let regChunk :: ParsecT Sources ParserState m Text
regChunk = ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
noneOf [Char
'\\',Char
'\n',Char
'&',Char
c]) ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar
let nestedChunk :: ParsecT Sources ParserState m Text
nestedChunk = (\Text
x -> (Char
c Char -> Text -> Text
`T.cons` Text
x) Text -> Char -> Text
`T.snoc` Char
c) (Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> ParsecT Sources ParserState m Text
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
quotedTitle Char
c
[Text] -> Text
T.unwords ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.words (Text -> [Text]) -> ([Text] -> Text) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill (ParsecT Sources ParserState m Text
nestedChunk ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
regChunk) ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
pEnder
abbrevKey :: PandocMonad m => MarkdownParser m (F Blocks)
abbrevKey :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
abbrevKey = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_abbreviations
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks))
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*'
MarkdownParser m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ((Char -> Bool) -> ParsecT Sources ParserState 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
'\n'))
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
noteMarker :: PandocMonad m => MarkdownParser m Text
noteMarker :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
noteMarker = FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"[^" ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar ((Char -> Bool) -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Char
'\r',Char
'\n',Char
'\t',Char
' ',Char
'^',Char
'[',Char
']']))
(Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']')
rawLine :: PandocMonad m => MarkdownParser m Text
rawLine :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawLine = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByDivCloser
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces MarkdownParser m Int
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
noteMarker
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentSpaces
ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
rawLines :: PandocMonad m => MarkdownParser m Text
rawLines :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawLines = do
Text
first <- MarkdownParser m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
[Text]
rest <- MarkdownParser m Text -> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawLine
Text -> MarkdownParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> MarkdownParser m Text) -> Text -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines (Text
firstText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
rest)
noteBlock :: PandocMonad m => MarkdownParser m (F Blocks)
noteBlock :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
noteBlock = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_footnotes
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks))
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
SourcePos
pos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces
Text
ref <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
noteMarker
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
MarkdownParser m Text -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentSpaces
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateInNote = True }
Text
first <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawLines
[Text]
rest <- MarkdownParser m Text -> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MarkdownParser m Text -> ParsecT Sources ParserState m [Text])
-> MarkdownParser m Text -> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m Text -> MarkdownParser m Text)
-> MarkdownParser m Text -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentSpaces MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawLines
let raw :: Text
raw = [Text] -> Text
T.unlines (Text
firstText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
rest) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
MarkdownParser m Text -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MarkdownParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Future ParserState Blocks
parsed <- MarkdownParser m (Future ParserState Blocks)
-> Text -> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks Text
raw
Map Text (SourcePos, Future ParserState Blocks)
oldnotes <- ParserState -> Map Text (SourcePos, Future ParserState Blocks)
stateNotes' (ParserState -> Map Text (SourcePos, Future ParserState Blocks))
-> ParsecT Sources ParserState m ParserState
-> ParsecT
Sources
ParserState
m
(Map Text (SourcePos, Future ParserState Blocks))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
case Text
-> Map Text (SourcePos, Future ParserState Blocks)
-> Maybe (SourcePos, Future ParserState Blocks)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
ref Map Text (SourcePos, Future ParserState Blocks)
oldnotes of
Just (SourcePos, Future ParserState Blocks)
_ -> LogMessage -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage -> ParsecT Sources ParserState m ())
-> LogMessage -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
DuplicateNoteReference Text
ref SourcePos
pos
Maybe (SourcePos, Future ParserState Blocks)
Nothing -> () -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
s -> ParserState
s { stateNotes' =
M.insert ref (pos, parsed) oldnotes,
stateInNote = False }
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Future ParserState Blocks
forall a. Monoid a => a
mempty
parseBlocks :: PandocMonad m => MarkdownParser m (F Blocks)
parseBlocks :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks = [Future ParserState Blocks] -> Future ParserState Blocks
forall a. Monoid a => [a] -> a
mconcat ([Future ParserState Blocks] -> Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
block ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
block :: PandocMonad m => MarkdownParser m (F Blocks)
block :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
block = do
Future ParserState Blocks
res <- [MarkdownParser m (Future ParserState Blocks)]
-> MarkdownParser m (Future ParserState Blocks)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Future ParserState Blocks
forall a. Monoid a => a
mempty Future ParserState Blocks
-> ParsecT Sources ParserState m Text
-> MarkdownParser m (Future ParserState Blocks)
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
codeBlockFenced
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
yamlMetaBlock'
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
bulletList
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
divHtml
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
divFenced
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
header
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
lhsCodeBlock
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
htmlBlock
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
table
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
codeBlockIndented
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
rawTeXBlock
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
lineBlock
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
blockQuote
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *) st.
PandocMonad m =>
ParsecT Sources st m (Future ParserState Blocks)
hrule
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
orderedList
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
definitionList
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
noteBlock
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
referenceKey
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
abbrevKey
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
para
, MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
plain
] MarkdownParser m (Future ParserState Blocks)
-> FilePath -> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> FilePath -> ParsecT s u m a
<?> FilePath
"block"
Text -> ParsecT Sources ParserState 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 -> [Block]) -> Blocks -> [Block]
forall a b. (a -> b) -> a -> b
$ Future ParserState Blocks -> ParserState -> Blocks
forall s a. Future s a -> s -> a
runF Future ParserState Blocks
res ParserState
defaultParserState)
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Future ParserState Blocks
res
header :: PandocMonad m => MarkdownParser m (F Blocks)
= MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
setextHeader MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
atxHeader MarkdownParser m (Future ParserState Blocks)
-> FilePath -> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> FilePath -> ParsecT s u m a
<?> FilePath
"header"
atxChar :: PandocMonad m => MarkdownParser m Char
atxChar :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
atxChar = do
Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT Sources ParserState 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 ParserState m b
getOption ReaderOptions -> Extensions
readerExtensions
Char -> MarkdownParser m Char
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Char -> MarkdownParser m Char) -> Char -> MarkdownParser m Char
forall a b. (a -> b) -> a -> b
$ if Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_literate_haskell Extensions
exts
then Char
'='
else Char
'#'
atxHeader :: PandocMonad m => MarkdownParser m (F Blocks)
= ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
Int
level <- (FilePath -> Int)
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Int
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (MarkdownParser m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
atxChar MarkdownParser m Char
-> (Char -> ParsecT Sources ParserState m FilePath)
-> ParsecT Sources ParserState m FilePath
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MarkdownParser m Char -> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (MarkdownParser m Char -> ParsecT Sources ParserState m FilePath)
-> (Char -> MarkdownParser m Char)
-> Char
-> ParsecT Sources ParserState m FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> MarkdownParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char)
MarkdownParser m Char -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (MarkdownParser m Char -> ParsecT Sources ParserState m ())
-> MarkdownParser m Char -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_fancy_lists ParsecT Sources ParserState m ()
-> MarkdownParser m Char -> MarkdownParser m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(Char -> MarkdownParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'.' MarkdownParser m Char
-> MarkdownParser m Char -> MarkdownParser m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> MarkdownParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
')')
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_space_in_atx_header ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m Char -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy MarkdownParser m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
(F Inlines
text, Text
raw) <- ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines, Text))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall a b. (a -> b) -> a -> b
$ do
Bool
oldAllowLineBreaks <- ParserState -> Bool
stateAllowLineBreaks (ParserState -> Bool)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateAllowLineBreaks = False }
F Inlines
res <- F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
atxClosing ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline)
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateAllowLineBreaks = oldAllowLineBreaks }
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return F Inlines
res
Attr
attr <- ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
atxClosing
Attr
attr' <- Attr -> Inlines -> ParsecT Sources ParserState 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 Attr
attr (F Inlines -> ParserState -> Inlines
forall s a. Future s a -> s -> a
runF F Inlines
text ParserState
defaultParserState)
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_implicit_header_references
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> Attr -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> Attr -> MarkdownParser m ()
registerImplicitHeader Text
raw Attr
attr'
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Inlines -> Blocks
B.headerWith Attr
attr' Int
level (Inlines -> Blocks) -> F Inlines -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
text
atxClosing :: PandocMonad m => MarkdownParser m Attr
atxClosing :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
atxClosing = ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ do
Attr
attr' <- Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState 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
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_mmd_header_identifiers ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
mmdHeaderIdentifier)
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ())
-> (Char -> ParsecT Sources ParserState m Char)
-> Char
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ParsecT Sources ParserState 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 ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
atxChar
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Attr
attr <- Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState 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
attr'
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_header_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes)
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Attr -> ParsecT Sources ParserState m Attr
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Attr
attr
setextHeaderEnd :: PandocMonad m => MarkdownParser m Attr
= ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ do
Attr
attr <- Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState 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 Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_mmd_header_identifiers ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
mmdHeaderIdentifier)
ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_header_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes)
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Attr -> ParsecT Sources ParserState m Attr
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Attr
attr
mmdHeaderIdentifier :: PandocMonad m => MarkdownParser m Attr
= do
(F Inlines
_, Text
raw) <- MarkdownParser m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference
let raw' :: Text
raw' = Text -> Text
trim (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
stripFirstAndLast Text
raw
let ident :: Text
ident = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toLower Text
raw'
let attr :: (Text, [a], [a])
attr = (Text
ident, [], [])
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_implicit_header_references
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> Attr -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> Attr -> MarkdownParser m ()
registerImplicitHeader Text
raw' Attr
forall {a} {a}. (Text, [a], [a])
attr
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Attr -> MarkdownParser m Attr
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Attr
forall {a} {a}. (Text, [a], [a])
attr
setextHeader :: PandocMonad m => MarkdownParser m (F Blocks)
= ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
setextHChars) ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
(F Inlines
text, Text
raw) <- ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines, Text))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall a b. (a -> b) -> a -> b
$ do
Bool
oldAllowLineBreaks <- ParserState -> Bool
stateAllowLineBreaks (ParserState -> Bool)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateAllowLineBreaks = False }
F Inlines
res <- F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
setextHeaderEnd ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline)
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateAllowLineBreaks = oldAllowLineBreaks }
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return F Inlines
res
Attr
attr <- ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
setextHeaderEnd
Char
underlineChar <- FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
setextHChars
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
underlineChar)
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
let level :: Int
level = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (Char -> FilePath -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
elemIndex Char
underlineChar FilePath
setextHChars) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
Attr
attr' <- Attr -> Inlines -> ParsecT Sources ParserState 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 Attr
attr (F Inlines -> ParserState -> Inlines
forall s a. Future s a -> s -> a
runF F Inlines
text ParserState
defaultParserState)
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_implicit_header_references
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> Attr -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Text -> Attr -> MarkdownParser m ()
registerImplicitHeader Text
raw Attr
attr'
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Inlines -> Blocks
B.headerWith Attr
attr' Int
level (Inlines -> Blocks) -> F Inlines -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
text
registerImplicitHeader :: PandocMonad m => Text -> Attr -> MarkdownParser m ()
Text
raw attr :: Attr
attr@(Text
ident, [Text]
_, [Target]
_)
| Text -> Bool
T.null Text
raw = () -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
let key :: Key
key = Text -> Key
toKey (Text -> Key) -> Text -> Key
forall a b. (a -> b) -> a -> b
$ Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
raw Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
s ->
ParserState
s { stateHeaderKeys = M.insertWith (\(Target, Attr)
_new (Target, Attr)
old -> (Target, Attr)
old)
key (("#" <> ident,""), attr)
(stateHeaderKeys s) }
hrule :: PandocMonad m => ParsecT Sources st m (F Blocks)
hrule :: forall (m :: * -> *) st.
PandocMonad m =>
ParsecT Sources st m (Future ParserState Blocks)
hrule = ParsecT Sources st m (Future ParserState Blocks)
-> ParsecT Sources st m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources st m (Future ParserState Blocks)
-> ParsecT Sources st m (Future ParserState Blocks))
-> ParsecT Sources st m (Future ParserState Blocks)
-> ParsecT Sources st m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources st m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Char
start <- (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 -> Bool
isHruleChar
Int -> ParsecT Sources st m Char -> ParsecT Sources st m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
2 (ParsecT Sources st m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources st m ()
-> ParsecT Sources st m Char -> ParsecT Sources st m Char
forall a b.
ParsecT Sources st m a
-> ParsecT Sources st m b -> ParsecT Sources st m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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
start)
ParsecT Sources st m Char -> ParsecT Sources st m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources st m Char
-> ParsecT Sources st m Char -> ParsecT Sources st m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> 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
start)
ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
ParsecT Sources st m Text -> ParsecT Sources st m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources st m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Future ParserState Blocks
-> ParsecT Sources st m (Future ParserState Blocks)
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources st m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources st m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
B.horizontalRule
indentedLine :: PandocMonad m => MarkdownParser m Text
indentedLine :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentedLine = MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentSpaces MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLineNewline
blockDelimiter :: PandocMonad m
=> (Char -> Bool)
-> Maybe Int
-> ParsecT Sources ParserState m Int
blockDelimiter :: forall (m :: * -> *).
PandocMonad m =>
(Char -> Bool) -> Maybe Int -> ParsecT Sources ParserState m Int
blockDelimiter Char -> Bool
f Maybe Int
len = ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int)
-> ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces
Char
c <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ((Char -> Bool) -> ParsecT Sources ParserState 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
f)
case Maybe Int
len of
Just Int
l -> Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
l (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c) ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c) ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ParsecT Sources ParserState m Int
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
l
Maybe Int
Nothing -> (FilePath -> Int)
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Int
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
3) (Int -> Int) -> (FilePath -> Int) -> FilePath -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) (Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
3 (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c) ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c))
attributes :: PandocMonad m => MarkdownParser m Attr
attributes :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes = ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState 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 ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl
[Attr -> Attr]
attrs <- ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m [Attr -> Attr]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
attribute ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl)
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'}'
Attr -> ParsecT Sources ParserState m Attr
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Attr -> ParsecT Sources ParserState m Attr)
-> Attr -> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ (Attr -> (Attr -> Attr) -> Attr) -> Attr -> [Attr -> Attr] -> Attr
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Attr
x Attr -> Attr
f -> Attr -> Attr
f Attr
x) Attr
nullAttr [Attr -> Attr]
attrs
attribute :: PandocMonad m => MarkdownParser m (Attr -> Attr)
attribute :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
attribute = MarkdownParser m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
identifierAttr MarkdownParser m (Attr -> Attr)
-> MarkdownParser m (Attr -> Attr)
-> MarkdownParser m (Attr -> Attr)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
classAttr MarkdownParser m (Attr -> Attr)
-> MarkdownParser m (Attr -> Attr)
-> MarkdownParser m (Attr -> Attr)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
keyValAttr MarkdownParser m (Attr -> Attr)
-> MarkdownParser m (Attr -> Attr)
-> MarkdownParser m (Attr -> Attr)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
specialAttr
identifier :: PandocMonad m => MarkdownParser m Text
identifier :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
identifier = do
Char
first <- ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter
FilePath
rest <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
"-_:."
Text -> MarkdownParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> MarkdownParser m Text) -> Text -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack (Char
firstChar -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
rest)
identifierAttr :: PandocMonad m => MarkdownParser m (Attr -> Attr)
identifierAttr :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
identifierAttr = ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr))
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'#'
Text
result <- FilePath -> Text
T.pack (FilePath -> Text)
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
"-_:.")
(Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr))
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ \(Text
_,[Text]
cs,[Target]
kvs) -> (Text
result,[Text]
cs,[Target]
kvs)
classAttr :: PandocMonad m => MarkdownParser m (Attr -> Attr)
classAttr :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
classAttr = ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr))
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'.'
Text
result <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
identifier
(Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr))
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ \(Text
id',[Text]
cs,[Target]
kvs) -> (Text
id',[Text]
cs [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
result],[Target]
kvs)
keyValAttr :: PandocMonad m => MarkdownParser m (Attr -> Attr)
keyValAttr :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
keyValAttr = ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr))
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ do
Text
key <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
identifier
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'='
Text
val <- [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text] -> MarkdownParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> MarkdownParser m Text
-> ParsecT Sources ParserState m [Text]
forall end s (m :: * -> *) st t a.
(Show end, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m t
-> ParsecT s st m end -> ParsecT s st m a -> ParsecT s st m [a]
enclosed (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"') (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"') MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar
MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text] -> MarkdownParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> MarkdownParser m Text
-> ParsecT Sources ParserState m [Text]
forall end s (m :: * -> *) st t a.
(Show end, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m t
-> ParsecT s st m end -> ParsecT s st m a -> ParsecT s st m [a]
enclosed (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\'') (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\'') MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar
MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text
"" Text
-> ParsecT Sources ParserState m FilePath -> MarkdownParser m Text
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"\"\""))
MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text
"" Text
-> ParsecT Sources ParserState m FilePath -> MarkdownParser m Text
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"''"))
MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char -> MarkdownParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar (ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
escapedChar' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
noneOf FilePath
" \t\n\r}")
(Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr))
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ \(Text
id',[Text]
cs,[Target]
kvs) ->
case Text
key of
Text
"id" -> (Text
val,[Text]
cs,[Target]
kvs)
Text
"class" -> (Text
id',[Text]
cs [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ Text -> [Text]
T.words Text
val,[Target]
kvs)
Text
_ -> (Text
id',[Text]
cs,[Target]
kvs [Target] -> [Target] -> [Target]
forall a. [a] -> [a] -> [a]
++ [(Text
key,Text
val)])
specialAttr :: PandocMonad m => MarkdownParser m (Attr -> Attr)
specialAttr :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Attr -> Attr)
specialAttr = do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-'
(Attr -> Attr) -> MarkdownParser m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> MarkdownParser m (Attr -> Attr))
-> (Attr -> Attr) -> MarkdownParser m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ \(Text
id',[Text]
cs,[Target]
kvs) -> (Text
id',[Text]
cs [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"unnumbered"],[Target]
kvs)
rawAttribute :: PandocMonad m => MarkdownParser m Text
rawAttribute :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawAttribute = do
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'='
Text
format <- ParsecT Sources ParserState m Char -> MarkdownParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (ParsecT Sources ParserState m Char -> MarkdownParser m Text)
-> ParsecT Sources ParserState m Char -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (\Char
c -> Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> FilePath -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'-', Char
'_'])
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'}'
Text -> MarkdownParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
format
codeBlockFenced :: PandocMonad m => MarkdownParser m (F Blocks)
codeBlockFenced :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
codeBlockFenced = ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
Text
indentchars <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
nonindentSpaces
let indentLevel :: Int
indentLevel = Text -> Int
T.length Text
indentchars
Char
c <- (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_fenced_code_blocks ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState 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 ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_backtick_code_blocks ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState 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 ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'`'))
Int
size <- (Char -> Bool) -> Maybe Int -> ParsecT Sources ParserState m Int
forall (m :: * -> *).
PandocMonad m =>
(Char -> Bool) -> Maybe Int -> ParsecT Sources ParserState m Int
blockDelimiter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c) Maybe Int
forall a. Maybe a
Nothing
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Either Text Attr
rawattr <-
(Text -> Either Text Attr
forall a b. a -> Either a b
Left (Text -> Either Text Attr)
-> MarkdownParser m Text
-> ParsecT Sources ParserState m (Either Text Attr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_attribute ParsecT Sources ParserState m ()
-> MarkdownParser m Text -> MarkdownParser m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawAttribute))
ParsecT Sources ParserState m (Either Text Attr)
-> ParsecT Sources ParserState m (Either Text Attr)
-> ParsecT Sources ParserState m (Either Text Attr)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Attr -> Either Text Attr
forall a b. b -> Either a b
Right (Attr -> Either Text Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m (Either Text Attr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
let pLangId :: ParsecT Sources st m Text
pLangId = ParsecT Sources st m Char -> ParsecT Sources st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (ParsecT Sources st m Char -> ParsecT Sources st m Text)
-> ((Char -> Bool) -> ParsecT Sources st m Char)
-> (Char -> Bool)
-> ParsecT Sources st m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (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 -> Bool) -> ParsecT Sources st m Text)
-> (Char -> Bool) -> ParsecT Sources st m Text
forall a b. (a -> b) -> a -> b
$ \Char
x ->
Char
x Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Char
'`', Char
'{', Char
'}'] Bool -> Bool -> Bool
&& Bool -> Bool
not (Char -> Bool
isSpace Char
x)
Maybe Text
mbLanguageId <- MarkdownParser m Text -> ParsecT Sources ParserState m (Maybe Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (Text -> Text
toLanguageId (Text -> Text) -> MarkdownParser m Text -> MarkdownParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m Text
forall {st}. ParsecT Sources st m Text
pLangId)
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Maybe Attr
mbAttr <- ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m (Maybe Attr)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_fenced_code_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes)
Attr -> ParsecT Sources ParserState m Attr
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Attr -> ParsecT Sources ParserState m Attr)
-> Attr -> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ case Maybe Attr
mbAttr of
Maybe Attr
Nothing -> (Text
"", Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList Maybe Text
mbLanguageId, [])
Just (Text
elementId, [Text]
classes, [Target]
attrs) ->
(Text
elementId, (([Text] -> [Text])
-> (Text -> [Text] -> [Text]) -> Maybe Text -> [Text] -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Text] -> [Text]
forall a. a -> a
id (:) Maybe Text
mbLanguageId) [Text]
classes, [Target]
attrs))
ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
Text
contents <- Text -> [Text] -> Text
T.intercalate Text
"\n" ([Text] -> Text)
-> ParsecT Sources ParserState m [Text] -> MarkdownParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
MarkdownParser m Text
-> MarkdownParser m Text -> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill (Int -> ParsecT Sources ParserState m Int
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m Int
gobbleAtMostSpaces Int
indentLevel ParsecT Sources ParserState m Int
-> MarkdownParser m Text -> MarkdownParser m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine)
(MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m Text -> MarkdownParser m Text)
-> MarkdownParser m Text -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ do
(Char -> Bool) -> Maybe Int -> ParsecT Sources ParserState m Int
forall (m :: * -> *).
PandocMonad m =>
(Char -> Bool) -> Maybe Int -> ParsecT Sources ParserState m Int
blockDelimiter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c) (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
size)
MarkdownParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines)
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks)
-> Blocks -> Future ParserState Blocks
forall a b. (a -> b) -> a -> b
$
case Either Text Attr
rawattr of
Left Text
syn -> Text -> Text -> Blocks
B.rawBlock Text
syn Text
contents
Right Attr
attr -> Attr -> Text -> Blocks
B.codeBlockWith Attr
attr Text
contents
toLanguageId :: Text -> Text
toLanguageId :: Text -> Text
toLanguageId = Text -> Text
T.toLower (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
forall {a}. (Eq a, IsString a) => a -> a
go
where go :: a -> a
go a
"c++" = a
"cpp"
go a
"objective-c" = a
"objectivec"
go a
x = a
x
codeBlockIndented :: PandocMonad m => MarkdownParser m (F Blocks)
codeBlockIndented :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
codeBlockIndented = do
[Text]
contents <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentedLine ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do Text
b <- ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Text
l <- ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentedLine
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources ParserState m Text)
-> Text -> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
l))
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
[Text]
classes <- (ReaderOptions -> [Text]) -> ParsecT Sources ParserState m [Text]
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 ParserState m b
getOption ReaderOptions -> [Text]
readerIndentedCodeClasses
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks)
-> Blocks -> Future ParserState Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Blocks
B.codeBlockWith (Text
"", [Text]
classes, []) (Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$
Text -> Text
stripTrailingNewlines (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text]
contents
lhsCodeBlock :: PandocMonad m => MarkdownParser m (F Blocks)
lhsCodeBlock :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
lhsCodeBlock = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_literate_haskell
(Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks)
-> (Text -> Blocks) -> Text -> Future ParserState Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Blocks
B.codeBlockWith (Text
"",[Text
"haskell",Text
"literate"],[]) (Text -> Future ParserState Blocks)
-> ParsecT Sources ParserState m Text
-> MarkdownParser m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
lhsCodeBlockBird ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
lhsCodeBlockLaTeX))
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks)
-> (Text -> Blocks) -> Text -> Future ParserState Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Blocks
B.codeBlockWith (Text
"",[Text
"haskell"],[]) (Text -> Future ParserState Blocks)
-> ParsecT Sources ParserState m Text
-> MarkdownParser m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
lhsCodeBlockInverseBird)
lhsCodeBlockLaTeX :: PandocMonad m => MarkdownParser m Text
lhsCodeBlockLaTeX :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
lhsCodeBlockLaTeX = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"\\begin{code}"
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
Text
contents <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath)
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"\\end{code}")
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources ParserState m Text)
-> Text -> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
stripTrailingNewlines Text
contents
lhsCodeBlockBird :: PandocMonad m => MarkdownParser m Text
lhsCodeBlockBird :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
lhsCodeBlockBird = Char -> MarkdownParser m Text
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
lhsCodeBlockBirdWith Char
'>'
lhsCodeBlockInverseBird :: PandocMonad m => MarkdownParser m Text
lhsCodeBlockInverseBird :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
lhsCodeBlockInverseBird = Char -> MarkdownParser m Text
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
lhsCodeBlockBirdWith Char
'<'
lhsCodeBlockBirdWith :: PandocMonad m => Char -> MarkdownParser m Text
lhsCodeBlockBirdWith :: forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
lhsCodeBlockBirdWith Char
c = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
SourcePos
pos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SourcePos -> Int
sourceColumn SourcePos
pos Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
1) (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> ParsecT Sources ParserState m ()
forall a. FilePath -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
Prelude.fail FilePath
"Not in first column"
[Text]
lns <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Text
forall (m :: * -> *) st.
PandocMonad m =>
Char -> ParsecT Sources st m Text
birdTrackLine Char
c
let lns' :: [Text]
lns' = if (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Text
ln -> Text -> Bool
T.null Text
ln Bool -> Bool -> Bool
|| Int -> Text -> Text
T.take Int
1 Text
ln Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
" ") [Text]
lns
then (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Text -> Text
T.drop Int
1) [Text]
lns
else [Text]
lns
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources ParserState m Text)
-> Text -> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
T.intercalate Text
"\n" [Text]
lns'
birdTrackLine :: PandocMonad m => Char -> ParsecT Sources st m Text
birdTrackLine :: forall (m :: * -> *) st.
PandocMonad m =>
Char -> ParsecT Sources st m Text
birdTrackLine Char
c = 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
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
c
Bool -> ParsecT Sources st m () -> ParsecT Sources st m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'<') (ParsecT Sources st m () -> ParsecT Sources st m ())
-> ParsecT Sources st m () -> ParsecT Sources st m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources st m Char -> ParsecT Sources st m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter
ParsecT Sources st m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
emailBlockQuoteStart :: PandocMonad m => MarkdownParser m Char
emailBlockQuoteStart :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
emailBlockQuoteStart = ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces MarkdownParser m Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' ')
emailBlockQuote :: PandocMonad m => MarkdownParser m [Text]
emailBlockQuote :: forall (m :: * -> *). PandocMonad m => MarkdownParser m [Text]
emailBlockQuote = ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ do
MarkdownParser m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
emailBlockQuoteStart
let emailLine :: ParsecT Sources ParserState m Text
emailLine = MarkdownParser m Char -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar (MarkdownParser m Char -> ParsecT Sources ParserState m Text)
-> MarkdownParser m Char -> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Char
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Char
nonEndline MarkdownParser m Char
-> MarkdownParser m Char -> MarkdownParser m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m Char -> MarkdownParser m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try
(MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
endline MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m Char -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy MarkdownParser m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
emailBlockQuoteStart ParsecT Sources ParserState m ()
-> MarkdownParser m Char -> MarkdownParser m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Char -> MarkdownParser m Char
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Char
'\n')
let emailSep :: MarkdownParser m Char
emailSep = MarkdownParser m Char -> MarkdownParser m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline MarkdownParser m Char
-> MarkdownParser m Char -> MarkdownParser m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
emailBlockQuoteStart)
Text
first <- ParsecT Sources ParserState m Text
emailLine
[Text]
rest <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Char
emailSep MarkdownParser m Char
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
emailLine
let raw :: [Text]
raw = Text
firstText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
rest
MarkdownParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline MarkdownParser m Char
-> MarkdownParser m Char -> MarkdownParser m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources ParserState m ()
-> MarkdownParser m Char -> MarkdownParser m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> MarkdownParser m Char
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Char
'\n')
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
[Text] -> ParsecT Sources ParserState m [Text]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
raw
blockQuote :: PandocMonad m => MarkdownParser m (F Blocks)
blockQuote :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
blockQuote = do
[Text]
raw <- MarkdownParser m [Text]
forall (m :: * -> *). PandocMonad m => MarkdownParser m [Text]
emailBlockQuote
Future ParserState Blocks
contents <- MarkdownParser m (Future ParserState Blocks)
-> Text -> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks (Text -> MarkdownParser m (Future ParserState Blocks))
-> Text -> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
T.intercalate Text
"\n" [Text]
raw Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n\n"
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks
B.blockQuote (Blocks -> Blocks)
-> Future ParserState Blocks -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future ParserState Blocks
contents
bulletListStart :: PandocMonad m => MarkdownParser m ()
bulletListStart :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
bulletListStart = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (() ()
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) st.
PandocMonad m =>
ParsecT Sources st m (Future ParserState Blocks)
hrule)
(Char -> Bool) -> ParsecT Sources ParserState 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
isBulletListMarker
Int -> ParsecT Sources ParserState m ()
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m ()
gobbleSpaces Int
1 ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Int -> MarkdownParser m Int
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m Int
gobbleAtMostSpaces Int
3 MarkdownParser m Int
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
orderedListStart :: PandocMonad m
=> Maybe (ListNumberStyle, ListNumberDelim)
-> MarkdownParser m (Int, ListNumberStyle, ListNumberDelim)
orderedListStart :: forall (m :: * -> *).
PandocMonad m =>
Maybe (ListNumberStyle, ListNumberDelim)
-> MarkdownParser m (Int, ListNumberStyle, ListNumberDelim)
orderedListStart Maybe (ListNumberStyle, ListNumberDelim)
mbstydelim = ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim))
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"p." ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit
(do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_fancy_lists
Int
start <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit ParsecT Sources ParserState m Text
-> (Text -> MarkdownParser m Int) -> MarkdownParser m Int
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> MarkdownParser m Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'.'
Int -> ParsecT Sources ParserState m ()
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m ()
gobbleSpaces Int
1 ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Int -> MarkdownParser m Int
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m Int
gobbleAtMostSpaces Int
3 MarkdownParser m Int
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar)
(Int, ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
start, ListNumberStyle
DefaultStyle, ListNumberDelim
DefaultDelim))
ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(do (Int
num, ListNumberStyle
style, ListNumberDelim
delim) <- ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> ((ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim))
-> Maybe (ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall s (m :: * -> *).
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s ParserState m (Int, ListNumberStyle, ListNumberDelim)
anyOrderedListMarker
(\(ListNumberStyle
sty,ListNumberDelim
delim) -> (\Int
start -> (Int
start,ListNumberStyle
sty,ListNumberDelim
delim)) (Int -> (Int, ListNumberStyle, ListNumberDelim))
-> MarkdownParser m Int
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ListNumberStyle -> ListNumberDelim -> MarkdownParser m Int
forall s (m :: * -> *).
(Stream s m Char, UpdateSourcePos s Char) =>
ListNumberStyle -> ListNumberDelim -> ParsecT s ParserState m Int
orderedListMarker ListNumberStyle
sty ListNumberDelim
delim)
Maybe (ListNumberStyle, ListNumberDelim)
mbstydelim
Int -> ParsecT Sources ParserState m ()
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m ()
gobbleSpaces Int
1 ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ListNumberDelim
delim ListNumberDelim -> ListNumberDelim -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberDelim
Period Bool -> Bool -> Bool
&& (ListNumberStyle
style ListNumberStyle -> ListNumberStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberStyle
UpperAlpha Bool -> Bool -> Bool
||
(ListNumberStyle
style ListNumberStyle -> ListNumberStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberStyle
UpperRoman Bool -> Bool -> Bool
&&
Int
num Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int
1, Int
5, Int
10, Int
50, Int
100, Int
500, Int
1000]))) (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$
() ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Int -> MarkdownParser m Int
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m Int
gobbleAtMostSpaces Int
3 MarkdownParser m Int
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar)
(Int, ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
num, ListNumberStyle
style, ListNumberDelim
delim))
listStart :: PandocMonad m => MarkdownParser m ()
listStart :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
listStart = MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
bulletListStart MarkdownParser m () -> MarkdownParser m () -> MarkdownParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> MarkdownParser m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Control.Monad.void (Maybe (ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall (m :: * -> *).
PandocMonad m =>
Maybe (ListNumberStyle, ListNumberDelim)
-> MarkdownParser m (Int, ListNumberStyle, ListNumberDelim)
orderedListStart Maybe (ListNumberStyle, ListNumberDelim)
forall a. Maybe a
Nothing)
listLine :: PandocMonad m => Int -> MarkdownParser m Text
listLine :: forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m Text
listLine Int
continuationIndent = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (do Int -> ParsecT Sources ParserState m ()
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m ()
gobbleSpaces Int
continuationIndent
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
listStart)
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByDivCloser
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (() ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Int -> ParsecT Sources ParserState m ()
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m ()
gobbleSpaces Int
continuationIndent)
ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
listLineCommon
listLineCommon :: PandocMonad m => MarkdownParser m Text
listLineCommon :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
listLineCommon = [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill
( ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ((Char -> Bool) -> ParsecT Sources ParserState 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 ParserState m Char)
-> (Char -> Bool) -> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ \Char
c -> Char
c Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Char
'\n', Char
'<', Char
'`'])
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((F Inlines, Text) -> Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m Text
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (F Inlines, Text) -> Text
forall a b. (a, b) -> b
snd (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
code)
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((Tag Text, Text) -> Text)
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m Text
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Tag Text] -> Text
forall str. StringLike str => [Tag str] -> str
renderTags ([Tag Text] -> Text)
-> ((Tag Text, Text) -> [Tag Text]) -> (Tag Text, Text) -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tag Text -> [Tag Text] -> [Tag Text]
forall a. a -> [a] -> [a]
:[]) (Tag Text -> [Tag Text])
-> ((Tag Text, Text) -> Tag Text) -> (Tag Text, Text) -> [Tag Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tag Text, Text) -> Tag Text
forall a b. (a, b) -> a
fst) ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isCommentTag)
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
) ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
rawListItem :: PandocMonad m
=> Bool
-> MarkdownParser m a
-> MarkdownParser m (Text, Int)
rawListItem :: forall (m :: * -> *) a.
PandocMonad m =>
Bool -> MarkdownParser m a -> MarkdownParser m (Text, Int)
rawListItem Bool
fourSpaceRule MarkdownParser m a
start = ParsecT Sources ParserState m (Text, Int)
-> ParsecT Sources ParserState m (Text, Int)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Text, Int)
-> ParsecT Sources ParserState m (Text, Int))
-> ParsecT Sources ParserState m (Text, Int)
-> ParsecT Sources ParserState m (Text, Int)
forall a b. (a -> b) -> a -> b
$ do
SourcePos
pos1 <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
MarkdownParser m a
start
SourcePos
pos2 <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
let continuationIndent :: Int
continuationIndent = if Bool
fourSpaceRule
then Int
4
else SourcePos -> Int
sourceColumn SourcePos
pos2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- SourcePos -> Int
sourceColumn SourcePos
pos1
Text
first <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
listLineCommon
[Text]
rest <- MarkdownParser m Text -> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (do ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
listStart
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (() ()
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
codeBlockFenced)
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
Int -> MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m Text
listLine Int
continuationIndent)
Text
blanks <- ParsecT Sources ParserState m Char -> MarkdownParser m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
let result :: Text
result = [Text] -> Text
T.unlines (Text
firstText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
rest) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
blanks
(Text, Int) -> ParsecT Sources ParserState m (Text, Int)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
result, Int
continuationIndent)
listContinuation :: PandocMonad m => Int -> MarkdownParser m Text
listContinuation :: forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m Text
listContinuation Int
continuationIndent = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
Text
x <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByDivCloser
Int -> ParsecT Sources ParserState m ()
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m ()
gobbleSpaces Int
continuationIndent
ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLineNewline
[Text]
xs <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByDivCloser
Int -> ParsecT Sources ParserState m ()
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m ()
gobbleSpaces Int
continuationIndent ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
listStart
ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLineNewline
Text
blanks <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources ParserState m Text)
-> Text -> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat (Text
xText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
xs) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
blanks
blanklines' :: PandocMonad m => MarkdownParser m Text
blanklines' :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
blanklines' = ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Text
checkDivCloser
where checkDivCloser :: ParsecT Sources ParserState m Text
checkDivCloser = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_fenced_divs
Int
divLevel <- ParserState -> Int
stateFencedDivLevel (ParserState -> Int)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Int
divLevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
divFenceEnd
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
notFollowedByDivCloser :: PandocMonad m => MarkdownParser m ()
notFollowedByDivCloser :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByDivCloser =
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_fenced_divs ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
do Int
divLevel <- ParserState -> Int
stateFencedDivLevel (ParserState -> Int)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Int
divLevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
divFenceEnd
notFollowedByHtmlCloser :: PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser = do
Maybe Text
inHtmlBlock <- ParserState -> Maybe Text
stateInHtmlBlock (ParserState -> Maybe Text)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
case Maybe Text
inHtmlBlock of
Just Text
t -> ParsecT Sources ParserState m (Tag Text, Text)
-> MarkdownParser m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (ParsecT Sources ParserState m (Tag Text, Text)
-> MarkdownParser m ())
-> ParsecT Sources ParserState m (Tag Text, Text)
-> MarkdownParser m ()
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose Text
t)
Maybe Text
Nothing -> () -> MarkdownParser m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
listItem :: PandocMonad m
=> Bool
-> MarkdownParser m a
-> MarkdownParser m (F Blocks)
listItem :: forall (m :: * -> *) a.
PandocMonad m =>
Bool
-> MarkdownParser m a
-> MarkdownParser m (Future ParserState Blocks)
listItem Bool
fourSpaceRule MarkdownParser m a
start = ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
ParserState
state <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let oldContext :: ParserContext
oldContext = ParserState -> ParserContext
stateParserContext ParserState
state
ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
state {stateParserContext = ListItemState}
(Text
first, Int
continuationIndent) <- Bool -> MarkdownParser m a -> MarkdownParser m (Text, Int)
forall (m :: * -> *) a.
PandocMonad m =>
Bool -> MarkdownParser m a -> MarkdownParser m (Text, Int)
rawListItem Bool
fourSpaceRule MarkdownParser m a
start
[Text]
continuations <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Int -> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => Int -> MarkdownParser m Text
listContinuation Int
continuationIndent)
let raw :: Text
raw = [Text] -> Text
T.concat (Text
firstText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
continuations)
Future ParserState Blocks
contents <- ParsecT Sources ParserState m (Future ParserState Blocks)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks Text
raw
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\ParserState
st -> ParserState
st {stateParserContext = oldContext})
Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT Sources ParserState 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 ParserState m b
getOption ReaderOptions -> Extensions
readerExtensions
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ [Block] -> Blocks
forall a. [a] -> Many a
B.fromList ([Block] -> Blocks) -> (Blocks -> [Block]) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extensions -> [Block] -> [Block]
taskListItemFromAscii Extensions
exts ([Block] -> [Block]) -> (Blocks -> [Block]) -> Blocks -> [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> [Block]
forall a. Many a -> [a]
B.toList (Blocks -> Blocks)
-> Future ParserState Blocks -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future ParserState Blocks
contents
orderedList :: PandocMonad m => MarkdownParser m (F Blocks)
orderedList :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
orderedList = ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
(Int
start, ListNumberStyle
style, ListNumberDelim
delim) <- ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (Maybe (ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall (m :: * -> *).
PandocMonad m =>
Maybe (ListNumberStyle, ListNumberDelim)
-> MarkdownParser m (Int, ListNumberStyle, ListNumberDelim)
orderedListStart Maybe (ListNumberStyle, ListNumberDelim)
forall a. Maybe a
Nothing)
Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ListNumberStyle
style ListNumberStyle -> [ListNumberStyle] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ListNumberStyle
DefaultStyle, ListNumberStyle
Decimal, ListNumberStyle
Example] Bool -> Bool -> Bool
&&
ListNumberDelim
delim ListNumberDelim -> [ListNumberDelim] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ListNumberDelim
DefaultDelim, ListNumberDelim
Period]) (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_fancy_lists
Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ListNumberStyle
style ListNumberStyle -> ListNumberStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberStyle
Example) (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_example_lists
Bool
fourSpaceRule <- (Bool
True Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_four_space_rule)
ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ListNumberStyle
style ListNumberStyle -> ListNumberStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberStyle
Example)
Future ParserState [Blocks]
items <- ([Future ParserState Blocks] -> Future ParserState [Blocks])
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks])
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall a b. (a -> b) -> a -> b
$ Bool
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) a.
PandocMonad m =>
Bool
-> MarkdownParser m a
-> MarkdownParser m (Future ParserState Blocks)
listItem Bool
fourSpaceRule
(Maybe (ListNumberStyle, ListNumberDelim)
-> ParsecT
Sources ParserState m (Int, ListNumberStyle, ListNumberDelim)
forall (m :: * -> *).
PandocMonad m =>
Maybe (ListNumberStyle, ListNumberDelim)
-> MarkdownParser m (Int, ListNumberStyle, ListNumberDelim)
orderedListStart ((ListNumberStyle, ListNumberDelim)
-> Maybe (ListNumberStyle, ListNumberDelim)
forall a. a -> Maybe a
Just (ListNumberStyle
style, ListNumberDelim
delim)))
Int
start' <- if ListNumberStyle
style ListNumberStyle -> ListNumberStyle -> Bool
forall a. Eq a => a -> a -> Bool
== ListNumberStyle
Example
then Int -> ParsecT Sources ParserState m Int
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
start
else (Int
start Int
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Int
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_startnum) ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int -> ParsecT Sources ParserState m Int
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
1
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ (Int, ListNumberStyle, ListNumberDelim) -> [Blocks] -> Blocks
B.orderedListWith (Int
start', ListNumberStyle
style, ListNumberDelim
delim) ([Blocks] -> Blocks)
-> Future ParserState [Blocks] -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Blocks] -> [Blocks])
-> Future ParserState [Blocks] -> Future ParserState [Blocks]
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Blocks] -> [Blocks]
compactify Future ParserState [Blocks]
items
bulletList :: PandocMonad m => MarkdownParser m (F Blocks)
bulletList :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
bulletList = do
Bool
fourSpaceRule <- (Bool
True Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_four_space_rule)
ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Future ParserState [Blocks]
items <- ([Future ParserState Blocks] -> Future ParserState [Blocks])
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b. (a -> b) -> a -> b
$ MarkdownParser m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (MarkdownParser m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks])
-> MarkdownParser m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall a b. (a -> b) -> a -> b
$ Bool
-> ParsecT Sources ParserState m ()
-> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *) a.
PandocMonad m =>
Bool
-> MarkdownParser m a
-> MarkdownParser m (Future ParserState Blocks)
listItem Bool
fourSpaceRule ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
bulletListStart
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
B.bulletList ([Blocks] -> Blocks)
-> Future ParserState [Blocks] -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Blocks] -> [Blocks])
-> Future ParserState [Blocks] -> Future ParserState [Blocks]
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Blocks] -> [Blocks]
compactify Future ParserState [Blocks]
items
defListMarker :: PandocMonad m => MarkdownParser m ()
defListMarker :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
defListMarker = do
Text
sps <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
nonindentSpaces
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'~'
Int
tabStop <- (ReaderOptions -> Int) -> ParsecT Sources ParserState m Int
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 ParserState m b
getOption ReaderOptions -> Int
readerTabStop
let remaining :: Int
remaining = Int
tabStop Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Text -> Int
T.length Text
sps Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
if Int
remaining Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
remaining (Char -> ParsecT Sources ParserState 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 ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"\t" ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
else ParsecT Sources ParserState m FilePath
forall a. ParsecT Sources ParserState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
() -> MarkdownParser m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
definitionListItem :: PandocMonad m => Bool -> MarkdownParser m (F (Inlines, [Blocks]))
definitionListItem :: forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F (Inlines, [Blocks]))
definitionListItem Bool
compact = ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m (F (Inlines, [Blocks])))
-> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
forall a b. (a -> b) -> a -> b
$ do
Text
rawLine' <- ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
[Text]
raw <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ Bool -> ParsecT Sources ParserState m Text
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m Text
defRawBlock Bool
compact
F Inlines
term <- ParsecT Sources ParserState m (F Inlines)
-> Text -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' (F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines) Text
rawLine'
[Future ParserState Blocks]
contents <- (Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> [Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (ParsecT Sources ParserState m (Future ParserState Blocks)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks (Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> (Text -> Text)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n")) [Text]
raw
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
F (Inlines, [Blocks])
-> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F (Inlines, [Blocks])
-> ParsecT Sources ParserState m (F (Inlines, [Blocks])))
-> F (Inlines, [Blocks])
-> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
forall a b. (a -> b) -> a -> b
$ (Inlines -> [Blocks] -> (Inlines, [Blocks]))
-> F Inlines
-> Future ParserState [Blocks]
-> F (Inlines, [Blocks])
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) F Inlines
term ([Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [Future ParserState Blocks]
contents)
defRawBlock :: PandocMonad m => Bool -> MarkdownParser m Text
defRawBlock :: forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m Text
defRawBlock Bool
compact = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
Bool
hasBlank <- Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool)
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
defListMarker
Text
firstline <- ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLineNewline
let dline :: ParsecT Sources ParserState m Text
dline = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try
( do ParsecT Sources ParserState m Char -> MarkdownParser m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser
MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByDivCloser
if Bool
compact
then () () -> ParsecT Sources ParserState m Text -> MarkdownParser m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentSpaces
else (() () -> ParsecT Sources ParserState m Text -> MarkdownParser m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentSpaces)
MarkdownParser m () -> MarkdownParser m () -> MarkdownParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m () -> MarkdownParser m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
defListMarker
ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine )
[Text]
rawlines <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Text
dline
Text
cont <- ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Text] -> Text
T.concat (ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
Text
trailing <- Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Text
ln <- ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
indentSpaces ParsecT Sources ParserState m Text
-> MarkdownParser m () -> MarkdownParser m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char -> MarkdownParser m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline MarkdownParser m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
[Text]
lns <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Text
dline
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources ParserState m Text)
-> Text -> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ Text
trailing Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.unlines (Text
lnText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
lns)
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources ParserState m Text)
-> Text -> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
trimr (Text
firstline Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.unlines [Text]
rawlines Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cont) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
if Bool
hasBlank Bool -> Bool -> Bool
|| Bool -> Bool
not (Text -> Bool
T.null Text
cont) then Text
"\n\n" else Text
""
definitionList :: PandocMonad m => MarkdownParser m (F Blocks)
definitionList :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
definitionList = ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Control.Monad.void ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
table)) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
defListMarker)
ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
compactDefinitionList ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
normalDefinitionList
compactDefinitionList :: PandocMonad m => MarkdownParser m (F Blocks)
compactDefinitionList :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
compactDefinitionList = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_compact_definition_lists
Future ParserState [(Inlines, [Blocks])]
items <- ([F (Inlines, [Blocks])]
-> Future ParserState [(Inlines, [Blocks])])
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])]
-> ParsecT
Sources ParserState m (Future ParserState [(Inlines, [Blocks])])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [F (Inlines, [Blocks])] -> Future ParserState [(Inlines, [Blocks])]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [F (Inlines, [Blocks])]
-> ParsecT
Sources ParserState m (Future ParserState [(Inlines, [Blocks])]))
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])]
-> ParsecT
Sources ParserState m (Future ParserState [(Inlines, [Blocks])])
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])])
-> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])]
forall a b. (a -> b) -> a -> b
$ Bool -> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F (Inlines, [Blocks]))
definitionListItem Bool
True
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ [(Inlines, [Blocks])] -> Blocks
B.definitionList ([(Inlines, [Blocks])] -> Blocks)
-> Future ParserState [(Inlines, [Blocks])]
-> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([(Inlines, [Blocks])] -> [(Inlines, [Blocks])])
-> Future ParserState [(Inlines, [Blocks])]
-> Future ParserState [(Inlines, [Blocks])]
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
compactifyDL Future ParserState [(Inlines, [Blocks])]
items
normalDefinitionList :: PandocMonad m => MarkdownParser m (F Blocks)
normalDefinitionList :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
normalDefinitionList = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_definition_lists
Future ParserState [(Inlines, [Blocks])]
items <- ([F (Inlines, [Blocks])]
-> Future ParserState [(Inlines, [Blocks])])
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])]
-> ParsecT
Sources ParserState m (Future ParserState [(Inlines, [Blocks])])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [F (Inlines, [Blocks])] -> Future ParserState [(Inlines, [Blocks])]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [F (Inlines, [Blocks])]
-> ParsecT
Sources ParserState m (Future ParserState [(Inlines, [Blocks])]))
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])]
-> ParsecT
Sources ParserState m (Future ParserState [(Inlines, [Blocks])])
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])])
-> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
-> ParsecT Sources ParserState m [F (Inlines, [Blocks])]
forall a b. (a -> b) -> a -> b
$ Bool -> ParsecT Sources ParserState m (F (Inlines, [Blocks]))
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F (Inlines, [Blocks]))
definitionListItem Bool
False
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ [(Inlines, [Blocks])] -> Blocks
B.definitionList ([(Inlines, [Blocks])] -> Blocks)
-> Future ParserState [(Inlines, [Blocks])]
-> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future ParserState [(Inlines, [Blocks])]
items
para :: PandocMonad m => MarkdownParser m (F Blocks)
para :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
para = ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT Sources ParserState 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 ParserState m b
getOption ReaderOptions -> Extensions
readerExtensions
F Inlines
result <- F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines1
let figureOr :: (Inlines -> Blocks) -> Inlines -> Blocks
figureOr Inlines -> Blocks
constr Inlines
inlns =
case Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
inlns of
[Image Attr
attr [Inline]
figCaption (Text
src, Text
tit)]
| Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_implicit_figures Extensions
exts
, Bool -> Bool
not ([Inline] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
figCaption) -> do
Attr -> Inlines -> Text -> Text -> Blocks
implicitFigure Attr
attr ([Inline] -> Inlines
forall a. [a] -> Many a
B.fromList [Inline]
figCaption) Text
src Text
tit
[Inline]
_ -> Inlines -> Blocks
constr Inlines
inlns
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option ((Inlines -> Blocks) -> Inlines -> Blocks
figureOr Inlines -> Blocks
B.plain (Inlines -> Blocks) -> F Inlines -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
result)
(ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
(()
forall a. Monoid a => a
mempty ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_blank_before_blockquote
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
blockQuote)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_backtick_code_blocks
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
codeBlockFenced)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_blank_before_header
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
header)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_lists_without_preceding_blankline
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
inList
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
listStart)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_native_divs
Maybe Text
inHtmlBlock <- ParserState -> Maybe Text
stateInHtmlBlock (ParserState -> Maybe Text)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
case Maybe Text
inHtmlBlock of
Just Text
"div" -> () ()
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$
ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text, 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 Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose (Text
"div" :: Text)))
Maybe Text
_ -> ParsecT Sources ParserState m ()
forall a. ParsecT Sources ParserState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_fenced_divs
Int
divLevel <- ParserState -> Int
stateFencedDivLevel (ParserState -> Int)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
if Int
divLevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
divFenceEnd
else ParsecT Sources ParserState m ()
forall a. ParsecT Sources ParserState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ (Inlines -> Blocks) -> Inlines -> Blocks
figureOr Inlines -> Blocks
B.para (Inlines -> Blocks) -> F Inlines -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
result
plain :: PandocMonad m => MarkdownParser m (F Blocks)
plain :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
plain = (Inlines -> Blocks) -> F Inlines -> Future ParserState Blocks
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Blocks
B.plain (F Inlines -> Future ParserState Blocks)
-> (F Inlines -> F Inlines)
-> F Inlines
-> Future ParserState Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> Future ParserState Blocks)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines1
implicitFigure :: Attr -> Inlines -> Text -> Text -> Blocks
implicitFigure :: Attr -> Inlines -> Text -> Text -> Blocks
implicitFigure (Text
ident, [Text]
classes, [Target]
attribs) Inlines
capt Text
url Text
title =
let alt :: Inlines
alt = case Text
"alt" Text -> [Target] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
`lookup` [Target]
attribs of
Just Text
alt' -> Text -> Inlines
B.text Text
alt'
Maybe Text
_ -> Inlines
capt
attribs' :: [Target]
attribs' = (Target -> Bool) -> [Target] -> [Target]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"alt") (Text -> Bool) -> (Target -> Text) -> Target -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Target -> Text
forall a b. (a, b) -> a
fst) [Target]
attribs
figattr :: Attr
figattr = (Text
ident, [Text]
forall a. Monoid a => a
mempty, [Target]
forall a. Monoid a => a
mempty)
caption :: Caption
caption = Blocks -> Caption
B.simpleCaption (Blocks -> Caption) -> Blocks -> Caption
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.plain Inlines
capt
figbody :: Blocks
figbody = Inlines -> Blocks
B.plain (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith (Text
"", [Text]
classes, [Target]
attribs') Text
url Text
title Inlines
alt
in Attr -> Caption -> Blocks -> Blocks
B.figureWith Attr
figattr Caption
caption Blocks
figbody
htmlElement :: PandocMonad m => MarkdownParser m Text
htmlElement :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
htmlElement = MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawVerbatimBlock
MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
strictHtmlBlock
MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((Tag Text, Text) -> Text)
-> ParsecT Sources ParserState m (Tag Text, Text)
-> MarkdownParser m Text
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Tag Text, Text) -> Text
forall a b. (a, b) -> b
snd ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isBlockTag)
htmlBlock :: PandocMonad m => MarkdownParser m (F Blocks)
htmlBlock :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
htmlBlock = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_html
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do
(TagOpen Text
_ [Target]
attrs) <- ParsecT Sources ParserState m (Tag Text)
-> ParsecT Sources ParserState 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 Sources ParserState m (Tag Text)
-> ParsecT Sources ParserState m (Tag Text))
-> ParsecT Sources ParserState m (Tag Text)
-> ParsecT Sources ParserState m (Tag Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text, Text) -> Tag Text
forall a b. (a, b) -> a
fst ((Tag Text, Text) -> Tag Text)
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isBlockTag
Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks)
-> (Text -> Blocks) -> Text -> Future ParserState Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Blocks
B.rawBlock Text
"html" (Text -> Future ParserState Blocks)
-> ParsecT Sources ParserState m Text
-> MarkdownParser m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawVerbatimBlock
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_markdown_attribute
Bool
oldMarkdownAttribute <- ParserState -> Bool
stateMarkdownAttribute (ParserState -> Bool)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool
markdownAttribute <-
case Text -> [Target] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"markdown" [Target]
attrs of
Just Text
"0" -> Bool
False Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\ParserState
st -> ParserState
st{
stateMarkdownAttribute = False })
Just Text
_ -> Bool
True Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState (\ParserState
st -> ParserState
st{
stateMarkdownAttribute = True })
Maybe Text
Nothing -> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
oldMarkdownAttribute
Future ParserState Blocks
res <- if Bool
markdownAttribute
then MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
rawHtmlBlocks
else MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
htmlBlock'
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateMarkdownAttribute =
oldMarkdownAttribute }
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Future ParserState Blocks
res)
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_markdown_in_html_blocks ParsecT Sources ParserState m ()
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
rawHtmlBlocks))
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
htmlBlock'
htmlBlock' :: PandocMonad m => MarkdownParser m (F Blocks)
htmlBlock' :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
htmlBlock' = ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
Text
first <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
htmlElement
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
MarkdownParser m Text -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MarkdownParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ if Text -> Bool
T.null Text
first
then Future ParserState Blocks
forall a. Monoid a => a
mempty
else Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks)
-> Blocks -> Future ParserState Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Blocks
B.rawBlock Text
"html" Text
first
strictHtmlBlock :: PandocMonad m => MarkdownParser m Text
strictHtmlBlock :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
strictHtmlBlock = (Tag Text -> Bool) -> ParsecT Sources ParserState m Text
forall (m :: * -> *) st.
Monad m =>
(Tag Text -> Bool) -> ParsecT Sources st m Text
htmlInBalanced (Bool -> Bool
not (Bool -> Bool) -> (Tag Text -> Bool) -> Tag Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tag Text -> Bool
isInlineTag)
rawVerbatimBlock :: PandocMonad m => MarkdownParser m Text
rawVerbatimBlock :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawVerbatimBlock = (Tag Text -> Bool) -> ParsecT Sources ParserState m Text
forall (m :: * -> *) st.
Monad m =>
(Tag Text -> Bool) -> ParsecT Sources st m Text
htmlInBalanced Tag Text -> Bool
forall {a}. (Eq a, IsString a) => Tag a -> Bool
isVerbTag
where isVerbTag :: Tag a -> Bool
isVerbTag (TagOpen a
"pre" [Attribute a]
_) = Bool
True
isVerbTag (TagOpen a
"style" [Attribute a]
_) = Bool
True
isVerbTag (TagOpen a
"script" [Attribute a]
_) = Bool
True
isVerbTag (TagOpen a
"textarea" [Attribute a]
_) = Bool
True
isVerbTag Tag a
_ = Bool
False
rawTeXBlock :: PandocMonad m => MarkdownParser m (F Blocks)
rawTeXBlock :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
rawTeXBlock = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_tex
Blocks
result <- (Text -> Text -> Blocks
B.rawBlock Text
"tex" (Text -> Blocks) -> ([Text] -> Text) -> [Text] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trim (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.concat ([Text] -> Blocks)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>) (Text -> Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Text
rawConTeXtEnvironment ParsecT Sources ParserState m (Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m Text
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Text
spnl'))
ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> Text -> Blocks
B.rawBlock Text
"tex" (Text -> Blocks) -> ([Text] -> Text) -> [Text] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trim (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.concat ([Text] -> Blocks)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>) (Text -> Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
ParsecT Sources s m Text
rawLaTeXBlock ParsecT Sources ParserState m (Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m Text
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Text
spnl'))
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ case Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
result of
[RawBlock Format
_ Text
cs]
| (Char -> Bool) -> Text -> Bool
T.all (Char -> FilePath -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
' ',Char
'\t',Char
'\n']) Text
cs -> Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
[Block]
_ -> Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
result
rawHtmlBlocks :: PandocMonad m => MarkdownParser m (F Blocks)
rawHtmlBlocks :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
rawHtmlBlocks = do
(TagOpen Text
tagtype [Target]
_, Text
raw) <- (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isBlockTag
let selfClosing :: Bool
selfClosing = Text
"/>" Text -> Text -> Bool
`T.isSuffixOf` Text
raw
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Int
tabStop <- (ReaderOptions -> Int) -> ParsecT Sources ParserState m Int
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 ParserState m b
getOption ReaderOptions -> Int
readerTabStop
Int
indentlevel <- Int
-> ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Int
0 (ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int)
-> ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall a b. (a -> b) -> a -> b
$
do ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
[Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int)
-> ParsecT Sources ParserState m [Int]
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m [Int]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ( (Int
1 Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Int
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState 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 ParserState m Int
-> ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Int
tabStop Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Int
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\t') )
Maybe Text
oldInHtmlBlock <- ParserState -> Maybe Text
stateInHtmlBlock (ParserState -> Maybe Text)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateInHtmlBlock = Just tagtype }
let closer :: ParsecT Sources ParserState m (Tag Text, Text)
closer = (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose Text
tagtype)
let block' :: MarkdownParser m (Future ParserState Blocks)
block' = MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks))
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
Int -> ParsecT Sources ParserState m Int
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m Int
gobbleAtMostSpaces Int
indentlevel
ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ParsecT Sources ParserState m (Tag Text, Text)
closer
MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
block
Future ParserState Blocks
contents <- if Bool
selfClosing
then Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Future ParserState Blocks
forall a. Monoid a => a
mempty
else [Future ParserState Blocks] -> Future ParserState Blocks
forall a. Monoid a => [a] -> a
mconcat ([Future ParserState Blocks] -> Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> MarkdownParser m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MarkdownParser m (Future ParserState Blocks)
block'
Future ParserState Blocks
result <-
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try
(do Int -> ParsecT Sources ParserState m Int
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
Int -> ParsecT Sources st m Int
gobbleAtMostSpaces Int
indentlevel
(Tag Text
_, Text
rawcloser) <- ParsecT Sources ParserState m (Tag Text, Text)
closer
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Blocks
B.rawBlock Text
"html" (Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text
stripMarkdownAttribute Text
raw) Future ParserState Blocks
-> Future ParserState Blocks -> Future ParserState Blocks
forall a. Semigroup a => a -> a -> a
<>
Future ParserState Blocks
contents Future ParserState Blocks
-> Future ParserState Blocks -> Future ParserState Blocks
forall a. Semigroup a => a -> a -> a
<>
Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Blocks
B.rawBlock Text
"html" Text
rawcloser)))
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Blocks
B.rawBlock Text
"html" Text
raw) Future ParserState Blocks
-> Future ParserState Blocks -> Future ParserState Blocks
forall a. Semigroup a => a -> a -> a
<> Future ParserState Blocks
contents)
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateInHtmlBlock = oldInHtmlBlock }
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Future ParserState Blocks
result
stripMarkdownAttribute :: Text -> Text
stripMarkdownAttribute :: Text -> Text
stripMarkdownAttribute Text
s = [Tag Text] -> Text
renderTags' ([Tag Text] -> Text) -> [Tag Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Tag Text) -> [Tag Text] -> [Tag Text]
forall a b. (a -> b) -> [a] -> [b]
map Tag Text -> Tag Text
forall {a}. (Eq a, IsString a) => Tag a -> Tag a
filterAttrib ([Tag Text] -> [Tag Text]) -> [Tag Text] -> [Tag Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Tag Text]
forall str. StringLike str => str -> [Tag str]
parseTags Text
s
where filterAttrib :: Tag a -> Tag a
filterAttrib (TagOpen a
t [Attribute a]
as) = a -> [Attribute a] -> Tag a
forall str. str -> [Attribute str] -> Tag str
TagOpen a
t
[(a
k,a
v) | (a
k,a
v) <- [Attribute a]
as, a
k a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
"markdown"]
filterAttrib Tag a
x = Tag a
x
lineBlock :: PandocMonad m => MarkdownParser m (F Blocks)
lineBlock :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
lineBlock = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_line_blocks
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks))
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
[F Inlines]
lines' <- ParsecT Sources ParserState m [Text]
forall (m :: * -> *) st. Monad m => ParsecT Sources st m [Text]
lineBlockLines ParsecT Sources ParserState m [Text]
-> ([Text] -> ParsecT Sources ParserState m [F Inlines])
-> ParsecT Sources ParserState m [F Inlines]
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
(Text -> ParsecT Sources ParserState m (F Inlines))
-> [Text] -> ParsecT Sources ParserState m [F Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (ParsecT Sources ParserState m (F Inlines)
-> Text -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' (F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines))
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Blocks
B.lineBlock ([Inlines] -> Blocks) -> F [Inlines] -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [F Inlines] -> F [Inlines]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [F Inlines]
lines'
dashedLine :: PandocMonad m
=> Char
-> ParsecT Sources st m (Int, Int)
dashedLine :: forall (m :: * -> *) st.
PandocMonad m =>
Char -> ParsecT Sources st m (Int, Int)
dashedLine Char
ch = do
FilePath
dashes <- ParsecT Sources st m Char -> ParsecT Sources st m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (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
ch)
FilePath
sp <- ParsecT Sources st m Char -> ParsecT Sources st m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
let lengthDashes :: Int
lengthDashes = FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
dashes
lengthSp :: Int
lengthSp = FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
sp
(Int, Int) -> ParsecT Sources st m (Int, Int)
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
lengthDashes, Int
lengthDashes Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lengthSp)
simpleTableHeader :: PandocMonad m
=> Bool
-> MarkdownParser m (F [Blocks], [Alignment], [Int])
Bool
headless = ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int]))
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
forall a b. (a -> b) -> a -> b
$ do
Text
rawContent <- if Bool
headless
then Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
else ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
Text
initSp <- ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
nonindentSpaces
[(Int, Int)]
dashes <- ParsecT Sources ParserState m (Int, Int)
-> ParsecT Sources ParserState m [(Int, Int)]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState m (Int, Int)
forall (m :: * -> *) st.
PandocMonad m =>
Char -> ParsecT Sources st m (Int, Int)
dashedLine Char
'-')
ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
let ([Int]
lengths, [Int]
lines') = [(Int, Int)] -> ([Int], [Int])
forall a b. [(a, b)] -> ([a], [b])
unzip [(Int, Int)]
dashes
let indices :: [Int]
indices = (Int -> Int -> Int) -> Int -> [Int] -> [Int]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) (Text -> Int
T.length Text
initSp) [Int]
lines'
[Text]
rawHeads <- (Text -> [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Text] -> [Text]
forall a. HasCallStack => [a] -> [a]
tail ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Text -> [Text]
splitTextByIndices ([Int] -> [Int]
forall a. HasCallStack => [a] -> [a]
init [Int]
indices)) (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$
if Bool
headless
then ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
else Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
rawContent
let aligns :: [Alignment]
aligns = ([Text] -> Int -> Alignment) -> [[Text]] -> [Int] -> [Alignment]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith [Text] -> Int -> Alignment
alignType ((Text -> [Text]) -> [Text] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: []) [Text]
rawHeads) [Int]
lengths
let rawHeads' :: [Text]
rawHeads' = if Bool
headless
then []
else [Text]
rawHeads
Future ParserState [Blocks]
heads <- ([Future ParserState Blocks] -> Future ParserState [Blocks])
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence
(ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b. (a -> b) -> a -> b
$
(Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> [Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (ParsecT Sources ParserState m (Future ParserState Blocks)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ([Future ParserState Blocks] -> Future ParserState Blocks
forall a. Monoid a => [a] -> a
mconcat ([Future ParserState Blocks] -> Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
plain)(Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> (Text -> Text)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Text -> Text
trim) [Text]
rawHeads'
(Future ParserState [Blocks], [Alignment], [Int])
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState [Blocks]
heads, [Alignment]
aligns, [Int]
indices)
alignType :: [Text]
-> Int
-> Alignment
alignType :: [Text] -> Int -> Alignment
alignType [] Int
_ = Alignment
AlignDefault
alignType [Text]
strLst Int
len =
let nonempties :: [Text]
nonempties = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
trimr [Text]
strLst
(Bool
leftSpace, Bool
rightSpace) =
case (Text -> Int) -> [Text] -> [Text]
forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn Text -> Int
T.length [Text]
nonempties of
(Text
x:[Text]
_) -> (HasCallStack => Text -> Char
Text -> Char
T.head Text
x Char -> FilePath -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
' ', Char
'\t'], Text -> Int
T.length Text
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
len)
[] -> (Bool
False, Bool
False)
in case (Bool
leftSpace, Bool
rightSpace) of
(Bool
True, Bool
False) -> Alignment
AlignRight
(Bool
False, Bool
True) -> Alignment
AlignLeft
(Bool
True, Bool
True) -> Alignment
AlignCenter
(Bool
False, Bool
False) -> Alignment
AlignDefault
tableFooter :: PandocMonad m => MarkdownParser m Text
= ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces MarkdownParser m Int
-> ParsecT Sources ParserState m [(Int, Int)]
-> ParsecT Sources ParserState m [(Int, Int)]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (Int, Int)
-> ParsecT Sources ParserState m [(Int, Int)]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState m (Int, Int)
forall (m :: * -> *) st.
PandocMonad m =>
Char -> ParsecT Sources st m (Int, Int)
dashedLine Char
'-') ParsecT Sources ParserState m [(Int, Int)]
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
blanklines'
tableSep :: PandocMonad m => MarkdownParser m Char
tableSep :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
tableSep = ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces MarkdownParser m Int
-> ParsecT Sources ParserState m [(Int, Int)]
-> ParsecT Sources ParserState m [(Int, Int)]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (Int, Int)
-> ParsecT Sources ParserState m [(Int, Int)]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState m (Int, Int)
forall (m :: * -> *) st.
PandocMonad m =>
Char -> ParsecT Sources st m (Int, Int)
dashedLine Char
'-') ParsecT Sources ParserState m [(Int, Int)]
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n'
rawTableLine :: PandocMonad m
=> [Int]
-> MarkdownParser m [Text]
rawTableLine :: forall (m :: * -> *).
PandocMonad m =>
[Int] -> MarkdownParser m [Text]
rawTableLine [Int]
indices = do
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
blanklines' ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
tableFooter)
Text
line <- ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
[Text] -> MarkdownParser m [Text]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> MarkdownParser m [Text])
-> [Text] -> MarkdownParser m [Text]
forall a b. (a -> b) -> a -> b
$ (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
trim ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. HasCallStack => [a] -> [a]
tail ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$
[Int] -> Text -> [Text]
splitTextByIndices ([Int] -> [Int]
forall a. HasCallStack => [a] -> [a]
init [Int]
indices) Text
line
tableLine :: PandocMonad m
=> [Int]
-> MarkdownParser m (F [Blocks])
tableLine :: forall (m :: * -> *).
PandocMonad m =>
[Int] -> MarkdownParser m (Future ParserState [Blocks])
tableLine [Int]
indices = [Int] -> MarkdownParser m [Text]
forall (m :: * -> *).
PandocMonad m =>
[Int] -> MarkdownParser m [Text]
rawTableLine [Int]
indices MarkdownParser m [Text]
-> ([Text]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
([Future ParserState Blocks] -> Future ParserState [Blocks])
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ([Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks])
-> [Text]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> [Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (ParsecT Sources ParserState m (Future ParserState Blocks)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ([Future ParserState Blocks] -> Future ParserState Blocks
forall a. Monoid a => [a] -> a
mconcat ([Future ParserState Blocks] -> Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
plain))
multilineRow :: PandocMonad m
=> [Int]
-> MarkdownParser m (F [Blocks])
multilineRow :: forall (m :: * -> *).
PandocMonad m =>
[Int] -> MarkdownParser m (Future ParserState [Blocks])
multilineRow [Int]
indices = do
[[Text]]
colLines <- ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [[Text]]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ([Int] -> ParsecT Sources ParserState m [Text]
forall (m :: * -> *).
PandocMonad m =>
[Int] -> MarkdownParser m [Text]
rawTableLine [Int]
indices)
let cols :: [Text]
cols = ([Text] -> Text) -> [[Text]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map [Text] -> Text
T.unlines ([[Text]] -> [Text]) -> [[Text]] -> [Text]
forall a b. (a -> b) -> a -> b
$ [[Text]] -> [[Text]]
forall a. [[a]] -> [[a]]
transpose [[Text]]
colLines
([Future ParserState Blocks] -> Future ParserState [Blocks])
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> MarkdownParser m (Future ParserState [Blocks])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [Future ParserState Blocks]
-> MarkdownParser m (Future ParserState [Blocks]))
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> MarkdownParser m (Future ParserState [Blocks])
forall a b. (a -> b) -> a -> b
$ (Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> [Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (ParsecT Sources ParserState m (Future ParserState Blocks)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ([Future ParserState Blocks] -> Future ParserState Blocks
forall a. Monoid a => [a] -> a
mconcat ([Future ParserState Blocks] -> Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
plain)) [Text]
cols
tableCaption :: PandocMonad m => MarkdownParser m (F Inlines)
tableCaption :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
tableCaption = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_table_captions
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
MarkdownParser m Int
forall (m :: * -> *). PandocMonad m => MarkdownParser m Int
skipNonindentSpaces
(FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
":" ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m FilePath
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ((Char -> Bool) -> ParsecT Sources ParserState 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
isPunctuation)) ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf [Char
'T',Char
't'] ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"able:")
F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines1 MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m Text
-> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
simpleTable :: PandocMonad m
=> Bool
-> MarkdownParser m (F TableComponents)
simpleTable :: forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F TableComponents)
simpleTable Bool
headless = do
F TableComponents
tableComponents <-
TableNormalization
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
-> ([Int]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> MarkdownParser m (F TableComponents)
forall s (m :: * -> *) st (mf :: * -> *) sep end.
(Stream s m Char, UpdateSourcePos s Char, HasReaderOptions st,
Monad mf) =>
TableNormalization
-> ParsecT s st m (mf [Blocks], [Alignment], [Int])
-> ([Int] -> ParsecT s st m (mf [Blocks]))
-> ParsecT s st m sep
-> ParsecT s st m end
-> ParsecT s st m (mf TableComponents)
tableWith' TableNormalization
NormalizeHeader
(Bool
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
forall (m :: * -> *).
PandocMonad m =>
Bool
-> MarkdownParser
m (Future ParserState [Blocks], [Alignment], [Int])
simpleTableHeader Bool
headless) [Int]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall (m :: * -> *).
PandocMonad m =>
[Int] -> MarkdownParser m (Future ParserState [Blocks])
tableLine
(() -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
(if Bool
headless then ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
tableFooter else ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
tableFooter ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
blanklines')
let useDefaultColumnWidths :: TableComponents -> TableComponents
useDefaultColumnWidths TableComponents
tc =
let cs' :: [(Alignment, ColWidth)]
cs' = ((Alignment, ColWidth) -> (Alignment, ColWidth))
-> [(Alignment, ColWidth)] -> [(Alignment, ColWidth)]
forall a b. (a -> b) -> [a] -> [b]
map ((ColWidth -> ColWidth)
-> (Alignment, ColWidth) -> (Alignment, ColWidth)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (ColWidth -> ColWidth -> ColWidth
forall a b. a -> b -> a
const ColWidth
ColWidthDefault)) ([(Alignment, ColWidth)] -> [(Alignment, ColWidth)])
-> [(Alignment, ColWidth)] -> [(Alignment, ColWidth)]
forall a b. (a -> b) -> a -> b
$ TableComponents -> [(Alignment, ColWidth)]
tableColSpecs TableComponents
tc
in TableComponents
tc {tableColSpecs = cs'}
F TableComponents -> MarkdownParser m (F TableComponents)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F TableComponents -> MarkdownParser m (F TableComponents))
-> F TableComponents -> MarkdownParser m (F TableComponents)
forall a b. (a -> b) -> a -> b
$ TableComponents -> TableComponents
useDefaultColumnWidths (TableComponents -> TableComponents)
-> F TableComponents -> F TableComponents
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F TableComponents
tableComponents
multilineTable :: PandocMonad m
=> Bool
-> MarkdownParser m (F TableComponents)
multilineTable :: forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F TableComponents)
multilineTable Bool
headless =
TableNormalization
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
-> ([Int]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (F TableComponents)
forall s (m :: * -> *) st (mf :: * -> *) sep end.
(Stream s m Char, UpdateSourcePos s Char, HasReaderOptions st,
Monad mf) =>
TableNormalization
-> ParsecT s st m (mf [Blocks], [Alignment], [Int])
-> ([Int] -> ParsecT s st m (mf [Blocks]))
-> ParsecT s st m sep
-> ParsecT s st m end
-> ParsecT s st m (mf TableComponents)
tableWith' TableNormalization
NormalizeHeader (Bool
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
forall (m :: * -> *).
PandocMonad m =>
Bool
-> MarkdownParser
m (Future ParserState [Blocks], [Alignment], [Int])
multilineTableHeader Bool
headless)
[Int]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall (m :: * -> *).
PandocMonad m =>
[Int] -> MarkdownParser m (Future ParserState [Blocks])
multilineRow ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
tableFooter
multilineTableHeader :: PandocMonad m
=> Bool
-> MarkdownParser m (F [Blocks], [Alignment], [Int])
Bool
headless = ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int]))
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
forall a b. (a -> b) -> a -> b
$ do
Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
headless (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$
MarkdownParser m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
tableSep MarkdownParser m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m Char -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy MarkdownParser m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
[Text]
rawContent <- if Bool
headless
then [Text] -> ParsecT Sources ParserState m [Text]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> ParsecT Sources ParserState m [Text])
-> [Text] -> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
forall a. a -> [a]
repeat Text
""
else ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ MarkdownParser m Char -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy MarkdownParser m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
tableSep ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
Text
initSp <- ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
nonindentSpaces
[(Int, Int)]
dashes <- ParsecT Sources ParserState m (Int, Int)
-> ParsecT Sources ParserState m [(Int, Int)]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState m (Int, Int)
forall (m :: * -> *) st.
PandocMonad m =>
Char -> ParsecT Sources st m (Int, Int)
dashedLine Char
'-')
MarkdownParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
let ([Int]
lengths, [Int]
lines') = [(Int, Int)] -> ([Int], [Int])
forall a b. [(a, b)] -> ([a], [b])
unzip [(Int, Int)]
dashes
let indices :: [Int]
indices = (Int -> Int -> Int) -> Int -> [Int] -> [Int]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) (Text -> Int
T.length Text
initSp) [Int]
lines'
let indices' :: [Int]
indices' = case [Int] -> [Int]
forall a. [a] -> [a]
reverse [Int]
indices of
[] -> []
(Int
x:[Int]
xs) -> [Int] -> [Int]
forall a. [a] -> [a]
reverse (Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
xs)
[[Text]]
rawHeadsList <- if Bool
headless
then (Text -> [Text]) -> [Text] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[]) ([Text] -> [[Text]]) -> (Text -> [Text]) -> Text -> [[Text]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. HasCallStack => [a] -> [a]
tail ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Text -> [Text]
splitTextByIndices ([Int] -> [Int]
forall a. HasCallStack => [a] -> [a]
init [Int]
indices')
(Text -> [[Text]])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [[Text]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
else [[Text]] -> ParsecT Sources ParserState m [[Text]]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([[Text]] -> ParsecT Sources ParserState m [[Text]])
-> [[Text]] -> ParsecT Sources ParserState m [[Text]]
forall a b. (a -> b) -> a -> b
$ [[Text]] -> [[Text]]
forall a. [[a]] -> [[a]]
transpose ([[Text]] -> [[Text]]) -> [[Text]] -> [[Text]]
forall a b. (a -> b) -> a -> b
$ (Text -> [Text]) -> [Text] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map
([Text] -> [Text]
forall a. HasCallStack => [a] -> [a]
tail ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Text -> [Text]
splitTextByIndices ([Int] -> [Int]
forall a. HasCallStack => [a] -> [a]
init [Int]
indices'))
[Text]
rawContent
let aligns :: [Alignment]
aligns = ([Text] -> Int -> Alignment) -> [[Text]] -> [Int] -> [Alignment]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith [Text] -> Int -> Alignment
alignType [[Text]]
rawHeadsList [Int]
lengths
let rawHeads :: [Text]
rawHeads = if Bool
headless
then []
else ([Text] -> Text) -> [[Text]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ([Text] -> Text
T.unlines ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
trim) [[Text]]
rawHeadsList
Future ParserState [Blocks]
heads <- ([Future ParserState Blocks] -> Future ParserState [Blocks])
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b. (a -> b) -> a -> b
$
(Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> [Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (ParsecT Sources ParserState m (Future ParserState Blocks)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ([Future ParserState Blocks] -> Future ParserState Blocks
forall a. Monoid a => [a] -> a
mconcat ([Future ParserState Blocks] -> Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
plain)(Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> (Text -> Text)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Text -> Text
trim) [Text]
rawHeads
(Future ParserState [Blocks], [Alignment], [Int])
-> ParsecT
Sources
ParserState
m
(Future ParserState [Blocks], [Alignment], [Int])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState [Blocks]
heads, [Alignment]
aligns, [Int]
indices')
gridTable :: PandocMonad m
=> MarkdownParser m (F TableComponents)
gridTable :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F TableComponents)
gridTable = TableNormalization
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (F TableComponents)
forall (m :: * -> *) (mf :: * -> *) st.
(Monad m, Monad mf, HasReaderOptions st, HasLastStrPosition st) =>
TableNormalization
-> ParsecT Sources st m (mf Blocks)
-> ParsecT Sources st m (mf TableComponents)
gridTableWith' TableNormalization
NormalizeHeader ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
parseBlocks
pipeBreak :: PandocMonad m => MarkdownParser m ([Alignment], [Int])
pipeBreak :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m ([Alignment], [Int])
pipeBreak = ParsecT Sources ParserState m ([Alignment], [Int])
-> ParsecT Sources ParserState m ([Alignment], [Int])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ([Alignment], [Int])
-> ParsecT Sources ParserState m ([Alignment], [Int]))
-> ParsecT Sources ParserState m ([Alignment], [Int])
-> ParsecT Sources ParserState m ([Alignment], [Int])
forall a b. (a -> b) -> a -> b
$ do
MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
nonindentSpaces
Bool
openPipe <- (Bool
True Bool
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState 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 ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
(Alignment, Int)
first <- ParsecT Sources ParserState m (Alignment, Int)
forall (m :: * -> *) st.
PandocMonad m =>
ParsecT Sources st m (Alignment, Int)
pipeTableHeaderPart
[(Alignment, Int)]
rest <- ParsecT Sources ParserState m (Alignment, Int)
-> ParsecT Sources ParserState m [(Alignment, Int)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m (Alignment, Int)
-> ParsecT Sources ParserState m [(Alignment, Int)])
-> ParsecT Sources ParserState m (Alignment, Int)
-> ParsecT Sources ParserState m [(Alignment, Int)]
forall a b. (a -> b) -> a -> b
$ MarkdownParser m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
sepPipe MarkdownParser m ()
-> ParsecT Sources ParserState m (Alignment, Int)
-> ParsecT Sources ParserState m (Alignment, Int)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m (Alignment, Int)
forall (m :: * -> *) st.
PandocMonad m =>
ParsecT Sources st m (Alignment, Int)
pipeTableHeaderPart
Bool
closePipe <- (Bool
True Bool
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState 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 ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Bool -> MarkdownParser m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MarkdownParser m ()) -> Bool -> MarkdownParser m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not ([(Alignment, Int)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Alignment, Int)]
rest Bool -> Bool -> Bool
&& Bool -> Bool
not (Bool
openPipe Bool -> Bool -> Bool
|| Bool
closePipe))
ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
([Alignment], [Int])
-> ParsecT Sources ParserState m ([Alignment], [Int])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (([Alignment], [Int])
-> ParsecT Sources ParserState m ([Alignment], [Int]))
-> ([Alignment], [Int])
-> ParsecT Sources ParserState m ([Alignment], [Int])
forall a b. (a -> b) -> a -> b
$ [(Alignment, Int)] -> ([Alignment], [Int])
forall a b. [(a, b)] -> ([a], [b])
unzip ((Alignment, Int)
first(Alignment, Int) -> [(Alignment, Int)] -> [(Alignment, Int)]
forall a. a -> [a] -> [a]
:[(Alignment, Int)]
rest)
pipeTable :: PandocMonad m => MarkdownParser m (F TableComponents)
pipeTable :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F TableComponents)
pipeTable = ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents))
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall a b. (a -> b) -> a -> b
$ do
MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
nonindentSpaces
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar
([Text]
heads,([Alignment]
aligns, [Int]
seplengths)) <- (,) ([Text] -> ([Alignment], [Int]) -> ([Text], ([Alignment], [Int])))
-> ParsecT Sources ParserState m [Text]
-> ParsecT
Sources
ParserState
m
(([Alignment], [Int]) -> ([Text], ([Alignment], [Int])))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m [Text]
forall (m :: * -> *). PandocMonad m => MarkdownParser m [Text]
pipeTableRow ParsecT
Sources
ParserState
m
(([Alignment], [Int]) -> ([Text], ([Alignment], [Int])))
-> ParsecT Sources ParserState m ([Alignment], [Int])
-> ParsecT Sources ParserState m ([Text], ([Alignment], [Int]))
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m ([Alignment], [Int])
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m ([Alignment], [Int])
pipeBreak
let cellContents :: Text -> ParsecT Sources ParserState m (Future ParserState Blocks)
cellContents = ParsecT Sources ParserState m (Future ParserState Blocks)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
pipeTableCell (Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> (Text -> Text)
-> Text
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trim
let numcols :: Int
numcols = [Alignment] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Alignment]
aligns
let heads' :: [Text]
heads' = Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
take Int
numcols [Text]
heads
[[Text]]
lines' <- ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [[Text]]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m [Text]
forall (m :: * -> *). PandocMonad m => MarkdownParser m [Text]
pipeTableRow
let lines'' :: [[Text]]
lines'' = ([Text] -> [Text]) -> [[Text]] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
take Int
numcols) [[Text]]
lines'
let lineWidths :: [Int]
lineWidths = ([Text] -> Int) -> [[Text]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> ([Text] -> [Int]) -> [Text] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Int) -> [Text] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Int
forall a. HasChars a => a -> Int
realLength) ([Text]
heads' [Text] -> [[Text]] -> [[Text]]
forall a. a -> [a] -> [a]
: [[Text]]
lines'')
Int
columns <- (ReaderOptions -> Int) -> ParsecT Sources ParserState m Int
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 ParserState m b
getOption ReaderOptions -> Int
readerColumns
let widths :: [Double]
widths = if [Int] -> Int
forall (f :: * -> *) a. (Foldable f, Ord a, Bounded a) => f a -> a
maximumBounded ([Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
seplengths Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: [Int]
lineWidths) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
numcols Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
columns
then (Int -> Double) -> [Int] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
len ->
Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
seplengths))
[Int]
seplengths
else Int -> Double -> [Double]
forall a. Int -> a -> [a]
replicate ([Alignment] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Alignment]
aligns) Double
0.0
(Future ParserState [Blocks]
headCells :: F [Blocks]) <- [Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([Future ParserState Blocks] -> Future ParserState [Blocks])
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> [Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Text -> ParsecT Sources ParserState m (Future ParserState Blocks)
cellContents [Text]
heads'
(F [[Blocks]]
rows :: F [[Blocks]]) <- [Future ParserState [Blocks]] -> F [[Blocks]]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([Future ParserState [Blocks]] -> F [[Blocks]])
-> ParsecT Sources ParserState m [Future ParserState [Blocks]]
-> ParsecT Sources ParserState m (F [[Blocks]])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
([Text]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> [[Text]]
-> ParsecT Sources ParserState m [Future ParserState [Blocks]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (([Future ParserState Blocks] -> Future ParserState [Blocks])
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Future ParserState Blocks] -> Future ParserState [Blocks]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [Future ParserState Blocks]
-> ParsecT Sources ParserState m (Future ParserState [Blocks]))
-> ([Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks])
-> [Text]
-> ParsecT Sources ParserState m (Future ParserState [Blocks])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> ParsecT Sources ParserState m (Future ParserState Blocks))
-> [Text]
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Text -> ParsecT Sources ParserState m (Future ParserState Blocks)
cellContents) [[Text]]
lines''
F TableComponents
-> ParsecT Sources ParserState m (F TableComponents)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F TableComponents
-> ParsecT Sources ParserState m (F TableComponents))
-> F TableComponents
-> ParsecT Sources ParserState m (F TableComponents)
forall a b. (a -> b) -> a -> b
$
TableNormalization
-> [Alignment]
-> [Double]
-> [Blocks]
-> [[Blocks]]
-> TableComponents
toTableComponents' TableNormalization
NormalizeHeader [Alignment]
aligns [Double]
widths ([Blocks] -> [[Blocks]] -> TableComponents)
-> Future ParserState [Blocks]
-> Future ParserState ([[Blocks]] -> TableComponents)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future ParserState [Blocks]
headCells Future ParserState ([[Blocks]] -> TableComponents)
-> F [[Blocks]] -> F TableComponents
forall a b.
Future ParserState (a -> b)
-> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> F [[Blocks]]
rows
sepPipe :: PandocMonad m => MarkdownParser m ()
sepPipe :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
sepPipe = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
pipeTableRow :: PandocMonad m => MarkdownParser m [Text]
pipeTableRow :: forall (m :: * -> *). PandocMonad m => MarkdownParser m [Text]
pipeTableRow = ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
scanForPipe
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Bool
openPipe <- (Bool
True Bool
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState 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 ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
let chunk :: ParsecT Sources ParserState m ()
chunk = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
code ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
math ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
rawHtmlInline ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
escapedChar ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
rawLaTeXInline')
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
noneOf FilePath
"|\n\r")
[Text]
cells <- (([()], Text) -> Text
forall a b. (a, b) -> b
snd (([()], Text) -> Text)
-> ParsecT Sources ParserState m ([()], Text)
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m [()]
-> ParsecT Sources ParserState m ([()], Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [()]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m ()
chunk)) ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
`sepBy1` Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|'
Bool
closePipe <- (Bool
True Bool
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState 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 ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not ([Text] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
cells Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
&& Bool -> Bool
not (Bool
openPipe Bool -> Bool -> Bool
|| Bool
closePipe))
ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
[Text] -> ParsecT Sources ParserState m [Text]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
cells
pipeTableCell :: PandocMonad m => MarkdownParser m (F Blocks)
pipeTableCell :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
pipeTableCell =
(do F Inlines
result <- MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines1
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.plain (Inlines -> Blocks) -> F Inlines -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
result)
ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Future ParserState Blocks
forall a. Monoid a => a
mempty
pipeTableHeaderPart :: PandocMonad m => ParsecT Sources st m (Alignment, Int)
= ParsecT Sources st m (Alignment, Int)
-> ParsecT Sources st m (Alignment, Int)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources st m (Alignment, Int)
-> ParsecT Sources st m (Alignment, Int))
-> ParsecT Sources st m (Alignment, Int)
-> ParsecT Sources st m (Alignment, Int)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources st m Char -> ParsecT Sources st m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Maybe Char
left <- ParsecT Sources st m Char -> ParsecT Sources st m (Maybe Char)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (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
':')
FilePath
pipe <- ParsecT Sources st m Char -> ParsecT Sources st m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (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
'-')
Maybe Char
right <- ParsecT Sources st m Char -> ParsecT Sources st m (Maybe Char)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (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
':')
ParsecT Sources st m Char -> ParsecT Sources st m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
let len :: Int
len = FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
pipe Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> (Char -> Int) -> Maybe Char -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 (Int -> Char -> Int
forall a b. a -> b -> a
const Int
1) Maybe Char
left Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> (Char -> Int) -> Maybe Char -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 (Int -> Char -> Int
forall a b. a -> b -> a
const Int
1) Maybe Char
right
(Alignment, Int) -> ParsecT Sources st m (Alignment, Int)
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(case (Maybe Char
left,Maybe Char
right) of
(Maybe Char
Nothing,Maybe Char
Nothing) -> Alignment
AlignDefault
(Just Char
_,Maybe Char
Nothing) -> Alignment
AlignLeft
(Maybe Char
Nothing,Just Char
_) -> Alignment
AlignRight
(Just Char
_,Just Char
_) -> Alignment
AlignCenter, Int
len)
scanForPipe :: PandocMonad m => ParsecT Sources st m ()
scanForPipe :: forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
scanForPipe = do
Sources [(SourcePos, Text)]
inps <- ParsecT Sources st m Sources
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
let ln :: Text
ln = case [(SourcePos, Text)]
inps of
[] -> Text
""
((SourcePos
_,Text
t):(SourcePos
_,Text
t'):[(SourcePos, Text)]
_) | Text -> Bool
T.null Text
t -> Text
t'
((SourcePos
_,Text
t):[(SourcePos, Text)]
_) -> Text
t
case (Char -> Bool) -> Text -> Target
T.break (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'|') Text
ln of
(Text
_, Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'|', Text
_)) -> () -> ParsecT Sources st m ()
forall a. a -> ParsecT Sources st m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Target
_ -> ParsecT Sources st m ()
forall a. ParsecT Sources st m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
table :: PandocMonad m => MarkdownParser m (F Blocks)
table :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
table = ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
Maybe (F Inlines)
frontCaption <- Maybe (F Inlines)
-> ParsecT Sources ParserState m (Maybe (F Inlines))
-> ParsecT Sources ParserState m (Maybe (F Inlines))
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Maybe (F Inlines)
forall a. Maybe a
Nothing (F Inlines -> Maybe (F Inlines)
forall a. a -> Maybe a
Just (F Inlines -> Maybe (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (Maybe (F Inlines))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
tableCaption)
F TableComponents
tableComponents <-
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_pipe_tables ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
scanForPipe ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F TableComponents)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F TableComponents)
pipeTable)) ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_multiline_tables ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Bool -> ParsecT Sources ParserState m (F TableComponents)
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F TableComponents)
multilineTable Bool
False)) ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_simple_tables ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Bool -> ParsecT Sources ParserState m (F TableComponents)
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F TableComponents)
simpleTable Bool
True ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m (F TableComponents)
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F TableComponents)
simpleTable Bool
False)) ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_multiline_tables ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Bool -> ParsecT Sources ParserState m (F TableComponents)
forall (m :: * -> *).
PandocMonad m =>
Bool -> MarkdownParser m (F TableComponents)
multilineTable Bool
True)) ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_grid_tables ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m (F TableComponents)
-> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m (F TableComponents)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F TableComponents)
gridTable) ParsecT Sources ParserState m (F TableComponents)
-> FilePath -> ParsecT Sources ParserState m (F TableComponents)
forall s u (m :: * -> *) a.
ParsecT s u m a -> FilePath -> ParsecT s u m a
<?> FilePath
"table"
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
F Inlines
caption <- case Maybe (F Inlines)
frontCaption of
Maybe (F Inlines)
Nothing -> F Inlines
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty) ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
tableCaption
Just F Inlines
c -> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return F Inlines
c
Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks))
-> Future ParserState Blocks
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
Inlines
caption' <- F Inlines
caption
(TableComponents Attr
_attr Caption
_capt [(Alignment, ColWidth)]
colspecs TableHead
th [TableBody]
tb TableFoot
tf) <- F TableComponents
tableComponents
Blocks -> Future ParserState Blocks
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> Future ParserState Blocks)
-> Blocks -> Future ParserState Blocks
forall a b. (a -> b) -> a -> b
$ Caption
-> [(Alignment, ColWidth)]
-> TableHead
-> [TableBody]
-> TableFoot
-> Blocks
B.table (Blocks -> Caption
B.simpleCaption (Blocks -> Caption) -> Blocks -> Caption
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.plain Inlines
caption') [(Alignment, ColWidth)]
colspecs TableHead
th [TableBody]
tb TableFoot
tf
inlines :: PandocMonad m => MarkdownParser m (F Inlines)
inlines :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines = [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline
inlines1 :: PandocMonad m => MarkdownParser m (F Inlines)
inlines1 :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines1 = [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline
inline :: PandocMonad m => MarkdownParser m (F Inlines)
inline :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline = do
Char
c <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
((case Char
c of
Char
' ' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
whitespace
Char
'\t' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
whitespace
Char
'\n' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
endline
Char
'`' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
code
Char
'_' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
strongOrEmph
Char
'*' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
strongOrEmph
Char
'^' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
superscript MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlineNote
Char
'[' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
note MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
cite MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
bracketedSpan MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Attr -> Text -> Text -> Inlines -> Inlines)
-> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> MarkdownParser m (F Inlines)
wikilink Attr -> Text -> Text -> Inlines -> Inlines
B.linkWith MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
link
Char
'!' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
image
Char
'$' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
math
Char
'~' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
strikeout MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
subscript
Char
'=' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
mark
Char
'<' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
autoLink MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
spanHtml MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
rawHtmlInline MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
ltSign
Char
'\\' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
math MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
escapedNewline MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
escapedChar MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
rawLaTeXInline'
Char
'@' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
cite MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
exampleRef
Char
'"' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart
Char
'\'' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart
Char
'\8216' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart
Char
'\145' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart
Char
'\8220' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart
Char
'\147' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart
Char
'-' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
cite MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart
Char
'.' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart
Char
'&' -> Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> (Inline -> Inlines) -> Inline -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inline -> Inlines
forall a. a -> Many a
B.singleton (Inline -> F Inlines)
-> ParsecT Sources ParserState m Inline
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inline
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inline
charRef
Char
':' -> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
emoji
Char
_ -> MarkdownParser m (F Inlines)
forall a. ParsecT Sources ParserState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero)
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
bareURL
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
str
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
symbol) MarkdownParser m (F Inlines)
-> FilePath -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> FilePath -> ParsecT s u m a
<?> FilePath
"inline"
escapedChar' :: PandocMonad m => MarkdownParser m Char
escapedChar' :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
escapedChar' = ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\\'
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_all_symbols_escapable ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Char -> Bool) -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isAlphaNum))
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_angle_brackets_escapable ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
"\\`*_{}[]()>#+-.!~\"<>")
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
"\\`*_{}[]()>#+-.!"
escapedNewline :: PandocMonad m => MarkdownParser m (F Inlines)
escapedNewline :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
escapedNewline = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_escaped_line_breaks
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState 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 ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n')
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.linebreak
escapedChar :: PandocMonad m => MarkdownParser m (F Inlines)
escapedChar :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
escapedChar = do
Char
result <- MarkdownParser m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
escapedChar'
case Char
result of
Char
' ' -> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
"\160"
Char
_ -> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F 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
result
ltSign :: PandocMonad m => MarkdownParser m (F Inlines)
ltSign :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
ltSign = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_raw_html
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isBlockTag))
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<'
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
"<"
exampleRef :: PandocMonad m => MarkdownParser m (F Inlines)
exampleRef :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
exampleRef = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_example_lists
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'@'
Text
lab <- [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> ([FilePath] -> [Text]) -> [FilePath] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Text) -> [FilePath] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Text
T.pack ([FilePath] -> Text)
-> ParsecT Sources ParserState m [FilePath]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m [FilePath]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do Char
c <- Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-'
FilePath
cs <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum
FilePath -> ParsecT Sources ParserState m FilePath
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Char
cChar -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
cs)))
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
ParserState
st <- Future ParserState ParserState
forall s. Future s s
askF
Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ case Text -> Map Text Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
lab (ParserState -> Map Text Int
stateExamples ParserState
st) of
Just Int
n -> Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. Show a => a -> Text
tshow Int
n
Maybe Int
Nothing -> Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
"@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
lab
symbol :: PandocMonad m => MarkdownParser m (F Inlines)
symbol :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
symbol = do
Char
result <- FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
noneOf FilePath
"<\\\n\t "
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState 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 ParserState m ()
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (() ()
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
rawTeXBlock)
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\\')
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F 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
result
code :: PandocMonad m => MarkdownParser m (F Inlines)
code :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
code = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
FilePath
starts <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState 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 ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Text
result <- Text -> Text
trim (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.concat
([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill
( ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
noneOf FilePath
"`\n")
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (Char -> ParsecT Sources ParserState 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 ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n'
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
inList ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
listStart)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
" "))
(ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count (FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
starts) (Char -> ParsecT Sources ParserState 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 ParserState m FilePath
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'`'))
Either Text Attr
rawattr <-
(Text -> Either Text Attr
forall a b. a -> Either a b
Left (Text -> Either Text Attr)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (Either Text Attr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_attribute ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
rawAttribute))
ParsecT Sources ParserState m (Either Text Attr)
-> ParsecT Sources ParserState m (Either Text Attr)
-> ParsecT Sources ParserState m (Either Text Attr)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Attr -> Either Text Attr
forall a b. b -> Either a b
Right (Attr -> Either Text Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m (Either Text Attr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Text
"",[],[])
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_inline_code_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes))
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> ParsecT Sources ParserState m (F Inlines))
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$
case Either Text Attr
rawattr of
Left Text
syn -> Text -> Text -> Inlines
B.rawInline Text
syn (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$! Text
result
Right Attr
attr -> Attr -> Text -> Inlines
B.codeWith Attr
attr (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$! Text
result
math :: PandocMonad m => MarkdownParser m (F Inlines)
math :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
math = (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.displayMath (Text -> F Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m Text
forall st s (m :: * -> *).
(HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
mathDisplay ParsecT Sources ParserState m Text
-> (Text -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ParsecT Sources ParserState m Text
forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
Text -> ParsecT Sources s m Text
applyMacros))
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.math (Text -> F Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m Text
forall st s (m :: * -> *).
(HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
mathInline ParsecT Sources ParserState m Text
-> (Text -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ParsecT Sources ParserState m Text
forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
Text -> ParsecT Sources s m Text
applyMacros)) ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a s st (m :: * -> *).
Monoid a =>
ParsecT s st m a -> ParsecT s st m a -> ParsecT s st m a
<+?>
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_smart ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines
apostrophe)
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
space ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Char -> Bool) -> ParsecT Sources ParserState 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
isPunctuation))
enclosure :: PandocMonad m
=> Char
-> MarkdownParser m (F Inlines)
enclosure :: forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m (F Inlines)
enclosure Char
c = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_intraword_underscores
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'*')
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources ParserState m Bool
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m Bool
notAfterString)
Text
cs <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c)
(Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
B.str Text
cs) F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<>) (F Inlines -> F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
whitespace
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
case Text -> Int
T.length Text
cs of
Int
3 -> Char -> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m (F Inlines)
three Char
c
Int
2 -> Char -> F Inlines -> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> F Inlines -> MarkdownParser m (F Inlines)
two Char
c F Inlines
forall a. Monoid a => a
mempty
Int
1 -> Char -> F Inlines -> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> F Inlines -> MarkdownParser m (F Inlines)
one Char
c F Inlines
forall a. Monoid a => a
mempty
Int
_ -> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
cs)
ender :: PandocMonad m => Char -> Int -> MarkdownParser m ()
ender :: forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
n = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ do
Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
n (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c)
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'*')
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_intraword_underscores
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum
three :: PandocMonad m => Char -> MarkdownParser m (F Inlines)
three :: forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m (F Inlines)
three Char
c = do
F Inlines
contents <- [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
1) ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline)
(Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
3 ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines
B.strong (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
B.emph (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
contents))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
2 ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> F Inlines -> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> F Inlines -> MarkdownParser m (F Inlines)
one Char
c (Inlines -> Inlines
B.strong (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
contents))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
1 ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> F Inlines -> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> F Inlines -> MarkdownParser m (F Inlines)
two Char
c (Inlines -> Inlines
B.emph (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
contents))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack [Char
c,Char
c,Char
c]) F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> F Inlines
contents)
two :: PandocMonad m => Char -> F Inlines -> MarkdownParser m (F Inlines)
two :: forall (m :: * -> *).
PandocMonad m =>
Char -> F Inlines -> MarkdownParser m (F Inlines)
two Char
c F Inlines
prefix' = do
F Inlines
contents <- [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
2) ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline)
(Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
2 ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines
B.strong (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (F Inlines
prefix' F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> F Inlines
contents)))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack [Char
c,Char
c]) F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> (F Inlines
prefix' F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> F Inlines
contents))
one :: PandocMonad m => Char -> F Inlines -> MarkdownParser m (F Inlines)
one :: forall (m :: * -> *).
PandocMonad m =>
Char -> F Inlines -> MarkdownParser m (F Inlines)
one Char
c F Inlines
prefix' = do
F Inlines
contents <- [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ( (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
1) ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline)
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string [Char
c,Char
c] ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
1) ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Char -> F Inlines -> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> F Inlines -> MarkdownParser m (F Inlines)
two Char
c F Inlines
forall a. Monoid a => a
mempty) )
(Char -> Int -> ParsecT Sources ParserState m ()
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> MarkdownParser m ()
ender Char
c Int
1 ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos ParsecT Sources ParserState m ()
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines
B.emph (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (F Inlines
prefix' F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> F Inlines
contents)))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
c) F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> (F Inlines
prefix' F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> F Inlines
contents))
strongOrEmph :: PandocMonad m => MarkdownParser m (F Inlines)
strongOrEmph :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
strongOrEmph = Char -> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m (F Inlines)
enclosure Char
'*' MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> MarkdownParser m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m (F Inlines)
enclosure Char
'_'
inlinesBetween :: PandocMonad m
=> (Show b)
=> MarkdownParser m a
-> MarkdownParser m b
-> MarkdownParser m (F Inlines)
inlinesBetween :: forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
MarkdownParser m a
-> MarkdownParser m b -> MarkdownParser m (F Inlines)
inlinesBetween MarkdownParser m a
start MarkdownParser m b
end =
F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m a
start MarkdownParser m a
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F Inlines)
-> MarkdownParser m b -> ParsecT Sources ParserState m [F Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m (F Inlines)
inner MarkdownParser m b
end)
where inner :: ParsecT Sources ParserState m (F Inlines)
inner = ParsecT Sources ParserState m (F Inlines)
innerSpace ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (() ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
whitespace) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline)
innerSpace :: ParsecT Sources ParserState m (F Inlines)
innerSpace = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
whitespace ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MarkdownParser m b -> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' MarkdownParser m b
end
strikeout :: PandocMonad m => MarkdownParser m (F Inlines)
strikeout :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
strikeout = (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.strikeout (F Inlines -> F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_strikeout ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
-> MarkdownParser m FilePath
-> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
MarkdownParser m a
-> MarkdownParser m b -> MarkdownParser m (F Inlines)
inlinesBetween ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
strikeStart MarkdownParser m FilePath
forall {u}. ParsecT Sources u m FilePath
strikeEnd)
where strikeStart :: ParsecT Sources u m ()
strikeStart = FilePath -> ParsecT Sources u m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"~~" ParsecT Sources u m FilePath
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar
ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (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
'~')
strikeEnd :: ParsecT Sources u m FilePath
strikeEnd = ParsecT Sources u m FilePath -> ParsecT Sources u m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m FilePath -> ParsecT Sources u m FilePath)
-> ParsecT Sources u m FilePath -> ParsecT Sources u m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> ParsecT Sources u m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"~~"
mark :: PandocMonad m => MarkdownParser m (F Inlines)
mark :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
mark = (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> Inlines -> Inlines
B.spanWith (Text
"",[Text
"mark"],[])) (F Inlines -> F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_mark ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
-> MarkdownParser m FilePath
-> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
MarkdownParser m a
-> MarkdownParser m b -> MarkdownParser m (F Inlines)
inlinesBetween ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
markStart MarkdownParser m FilePath
forall {u}. ParsecT Sources u m FilePath
markEnd)
where markStart :: ParsecT Sources u m ()
markStart = FilePath -> ParsecT Sources u m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"==" ParsecT Sources u m FilePath
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar
ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (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
'=')
markEnd :: ParsecT Sources u m FilePath
markEnd = ParsecT Sources u m FilePath -> ParsecT Sources u m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m FilePath -> ParsecT Sources u m FilePath)
-> ParsecT Sources u m FilePath -> ParsecT Sources u m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> ParsecT Sources u m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"=="
superscript :: PandocMonad m => MarkdownParser m (F Inlines)
superscript :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
superscript = do
(Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.superscript (F Inlines -> F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'^'
[F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m [F Inlines]
regularSuperscript ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m [F Inlines]
mmdShortSuperscript))
where regularSuperscript :: ParsecT Sources ParserState m [F Inlines]
regularSuperscript = MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [F Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till (do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_superscript
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline) (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'^')
mmdShortSuperscript :: ParsecT Sources ParserState m [F Inlines]
mmdShortSuperscript = do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_short_subsuperscripts
Text
result <- FilePath -> Text
T.pack (FilePath -> Text)
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum
[F Inlines] -> ParsecT Sources ParserState m [F Inlines]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([F Inlines] -> ParsecT Sources ParserState m [F Inlines])
-> [F Inlines] -> ParsecT Sources ParserState m [F Inlines]
forall a b. (a -> b) -> a -> b
$ F Inlines -> [F Inlines]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> [F Inlines]) -> F Inlines -> [F Inlines]
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
result
subscript :: PandocMonad m => MarkdownParser m (F Inlines)
subscript :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
subscript = do
(Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.subscript (F Inlines -> F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'~'
[F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m [F Inlines]
regularSubscript ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m [F Inlines]
mmdShortSubscript))
where regularSubscript :: ParsecT Sources ParserState m [F Inlines]
regularSubscript = MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [F Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till (do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_subscript
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline) (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'~')
mmdShortSubscript :: ParsecT Sources ParserState m [F Inlines]
mmdShortSubscript = do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_short_subsuperscripts
Text
result <- FilePath -> Text
T.pack (FilePath -> Text)
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum
[F Inlines] -> ParsecT Sources ParserState m [F Inlines]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([F Inlines] -> ParsecT Sources ParserState m [F Inlines])
-> [F Inlines] -> ParsecT Sources ParserState m [F Inlines]
forall a b. (a -> b) -> a -> b
$ F Inlines -> [F Inlines]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> [F Inlines]) -> F Inlines -> [F Inlines]
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
result
whitespace :: PandocMonad m => MarkdownParser m (F Inlines)
whitespace :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
whitespace = ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m Inlines
lb ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
forall {u}. ParsecT Sources u m Inlines
regsp) ParsecT Sources ParserState m (F Inlines)
-> FilePath -> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> FilePath -> ParsecT s u m a
<?> FilePath
"whitespace"
where lb :: ParsecT Sources ParserState m Inlines
lb = ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
B.space (ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
endline ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.linebreak)
regsp :: ParsecT Sources u m Inlines
regsp = ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources u m ()
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
nonEndline :: PandocMonad m => ParsecT Sources st m Char
nonEndline :: forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Char
nonEndline = (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
'\n')
str :: PandocMonad m => MarkdownParser m (F Inlines)
str :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
str = do
!Text
result <- [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1
( FilePath -> Text
T.pack (FilePath -> Text)
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum)
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text
"." Text
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> ParsecT Sources ParserState 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 ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos
(do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_smart
Set Text
abbrevs <- (ReaderOptions -> Set Text)
-> ParsecT Sources ParserState m (Set Text)
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 ParserState m b
getOption ReaderOptions -> Set Text
readerAbbreviations
if Text
result Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
abbrevs
then MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do F Inlines
ils <- MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
whitespace
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (() ()
-> MarkdownParser m (F Inlines) -> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
cite ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> MarkdownParser m (F Inlines) -> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
note)
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Inlines
ils' <- F Inlines
ils
case Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
ils' of
[Inline
Space] ->
Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$! (Text -> Inlines
B.str Text
result Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
B.str Text
"\160")
[Inline]
_ -> Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$! (Text -> Inlines
B.str Text
result Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
ils'))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$! Text -> Inlines
B.str Text
result)
else F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$! Text -> Inlines
B.str Text
result))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$! Text -> Inlines
B.str Text
result)
endline :: PandocMonad m => MarkdownParser m (F Inlines)
endline :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
endline = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState ParsecT Sources ParserState m ParserState
-> (ParserState -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> (ParserState -> Bool)
-> ParserState
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserState -> Bool
stateAllowLineBreaks
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
inList ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
listStart)
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_lists_without_preceding_blankline ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
listStart
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_blank_before_blockquote ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
emailBlockQuoteStart
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_blank_before_header ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ())
-> (Char -> ParsecT Sources ParserState m Char)
-> Char
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ParsecT Sources ParserState 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 ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => MarkdownParser m Char
atxChar)
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_backtick_code_blocks ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (() ()
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState 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 ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m (Future ParserState Blocks)
-> ParsecT Sources ParserState m (Future ParserState Blocks)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
codeBlockFenced))
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByHtmlCloser
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
notFollowedByDivCloser
(ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return F Inlines
forall a. Monoid a => a
mempty)
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_hard_line_breaks ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.linebreak))
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_ignore_line_breaks ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return F Inlines
forall a. Monoid a => a
mempty)
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.softbreak))
reference :: PandocMonad m => MarkdownParser m (F Inlines, Text)
reference :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_footnotes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
noteMarker
ParsecT Sources ParserState m (F Inlines)
-> MarkdownParser m (F Inlines, Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw (ParsecT Sources ParserState m (F Inlines)
-> MarkdownParser m (F Inlines, Text))
-> ParsecT Sources ParserState m (F Inlines)
-> MarkdownParser m (F Inlines, Text)
forall a b. (a -> b) -> a -> b
$ F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *) a.
PandocMonad m =>
MarkdownParser m (F a) -> MarkdownParser m (F a)
inBalancedBrackets ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines
parenthesizedChars :: PandocMonad m => MarkdownParser m Text
parenthesizedChars :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
parenthesizedChars = do
Text
result <- Char -> Char -> MarkdownParser m Text -> MarkdownParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
Char -> Char -> ParsecT s st m Text -> ParsecT s st m Text
charsInBalanced Char
'(' Char
')' MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar
Text -> MarkdownParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> MarkdownParser m Text) -> Text -> MarkdownParser m Text
forall a b. (a -> b) -> a -> b
$ Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
result Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
source :: PandocMonad m => MarkdownParser m (Text, Text)
source :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Target
source = do
Char -> ParsecT Sources ParserState 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 ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
let urlChunk :: ParsecT Sources ParserState m Text
urlChunk =
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
parenthesizedChars
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
" )") ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar)
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
"\"')"))
let sourceURL :: ParsecT Sources ParserState m Text
sourceURL = [Text] -> Text
T.unwords ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.words (Text -> [Text]) -> ([Text] -> Text) -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Text
urlChunk
let betweenAngles :: ParsecT Sources ParserState m Text
betweenAngles = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
litChar (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>'))
Text
src <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Text
betweenAngles ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
sourceURL
Text
tit <- Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
linkTitle
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
')'
Target -> MarkdownParser m Target
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text
escapeURI (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
trimr Text
src, Text
tit)
linkTitle :: PandocMonad m => MarkdownParser m Text
linkTitle :: forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
linkTitle = Char -> MarkdownParser m Text
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
quotedTitle Char
'"' MarkdownParser m Text
-> MarkdownParser m Text -> MarkdownParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> MarkdownParser m Text
forall (m :: * -> *).
PandocMonad m =>
Char -> MarkdownParser m Text
quotedTitle Char
'\''
wikilink :: PandocMonad m
=> (Attr -> Text -> Text -> Inlines -> Inlines)
-> MarkdownParser m (F Inlines)
wikilink :: forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> MarkdownParser m (F Inlines)
wikilink Attr -> Text -> Text -> Inlines -> Inlines
constructor = do
Bool
titleAfter <-
(Bool
True Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_wikilinks_title_after_pipe) ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Bool
False Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_wikilinks_title_before_pipe)
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"[[" ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'[')
Text
raw <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath)
-> ParsecT Sources ParserState m FilePath
-> ParsecT Sources ParserState m FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"]]")
let (Text
title, Text
url) = case (Char -> Bool) -> Text -> Target
T.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'|') Text
raw of
(Text
before, Text
"") -> (Text
before, Text
before)
(Text
before, Text
after)
| Bool
titleAfter -> (Int -> Text -> Text
T.drop Int
1 Text
after, Text
before)
| Bool
otherwise -> (Text
before, Int -> Text -> Text
T.drop Int
1 Text
after)
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Bool
T.all (Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Char
'\n',Char
'\r',Char
'\f',Char
'\t']) Text
url
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> (Inlines -> F Inlines)
-> Inlines
-> MarkdownParser m (F Inlines)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> F Inlines)
-> (Inlines -> Inlines) -> Inlines -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attr -> Text -> Text -> Inlines -> Inlines
constructor Attr
nullAttr Text
url Text
"wikilink" (Inlines -> MarkdownParser m (F Inlines))
-> Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$
Text -> Inlines
B.text (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text
fromEntities Text
title
link :: PandocMonad m => MarkdownParser m (F Inlines)
link :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
link = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState -> Bool
stateAllowLinks ParserState
st
ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks = False }
(F Inlines
lab,Text
raw) <- MarkdownParser m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference
ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks = True }
(Attr -> Text -> Text -> Inlines -> Inlines)
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> F Inlines -> MarkdownParser m (F Inlines)
regLink Attr -> Text -> Text -> Inlines -> Inlines
B.linkWith F Inlines
lab ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Attr -> Text -> Text -> Inlines -> Inlines)
-> (F Inlines, Text) -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> (F Inlines, Text) -> MarkdownParser m (F Inlines)
referenceLink Attr -> Text -> Text -> Inlines -> Inlines
B.linkWith (F Inlines
lab,Text
raw)
bracketedSpan :: PandocMonad m => MarkdownParser m (F Inlines)
bracketedSpan :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
bracketedSpan = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_bracketed_spans
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
(F Inlines
lab,Text
_) <- MarkdownParser m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference
Attr
attr <- MarkdownParser m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
wrapSpan Attr
attr (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
lab
wrapSpan :: Attr -> Inlines -> Inlines
wrapSpan :: Attr -> Inlines -> Inlines
wrapSpan (Text
ident, [Text]
classes, [Target]
kvs) =
let (Maybe (Inlines -> Inlines)
initConst, [Target]
kvs') = case Text -> [Target] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"style" [Target]
kvs of
Just Text
s | Text -> Bool
isSmallCapsFontVariant Text
s ->
let kvsNoStyle :: [Target]
kvsNoStyle = [(Text
k, Text
v) | (Text
k, Text
v) <- [Target]
kvs, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"style"]
in ((Inlines -> Inlines) -> Maybe (Inlines -> Inlines)
forall a. a -> Maybe a
Just Inlines -> Inlines
B.smallcaps, [Target]
kvsNoStyle)
Maybe Text
_ -> (Maybe (Inlines -> Inlines)
forall a. Maybe a
Nothing, [Target]
kvs)
(Maybe (Inlines -> Inlines)
mConstr, [Text]
remainingClasses) = (Text
-> (Maybe (Inlines -> Inlines), [Text])
-> (Maybe (Inlines -> Inlines), [Text]))
-> (Maybe (Inlines -> Inlines), [Text])
-> [Text]
-> (Maybe (Inlines -> Inlines), [Text])
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Text
-> (Maybe (Inlines -> Inlines), [Text])
-> (Maybe (Inlines -> Inlines), [Text])
forall {a}.
(Eq a, IsString a) =>
a
-> (Maybe (Inlines -> Inlines), [a])
-> (Maybe (Inlines -> Inlines), [a])
go (Maybe (Inlines -> Inlines)
initConst, []) [Text]
classes
wrapInConstr :: (b -> c) -> Maybe (b -> b) -> b -> c
wrapInConstr b -> c
c = (b -> c) -> ((b -> b) -> b -> c) -> Maybe (b -> b) -> b -> c
forall b a. b -> (a -> b) -> Maybe a -> b
maybe b -> c
c (b -> c
c (b -> c) -> (b -> b) -> b -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)
go :: a
-> (Maybe (Inlines -> Inlines), [a])
-> (Maybe (Inlines -> Inlines), [a])
go a
cls (Maybe (Inlines -> Inlines)
accConstr, [a]
other) =
case a
cls of
a
"smallcaps" -> ((Inlines -> Inlines) -> Maybe (Inlines -> Inlines)
forall a. a -> Maybe a
Just ((Inlines -> Inlines) -> Maybe (Inlines -> Inlines))
-> (Inlines -> Inlines) -> Maybe (Inlines -> Inlines)
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines)
-> Maybe (Inlines -> Inlines) -> Inlines -> Inlines
forall {b} {c}. (b -> c) -> Maybe (b -> b) -> b -> c
wrapInConstr Inlines -> Inlines
B.smallcaps Maybe (Inlines -> Inlines)
accConstr, [a]
other)
a
"ul" -> ((Inlines -> Inlines) -> Maybe (Inlines -> Inlines)
forall a. a -> Maybe a
Just ((Inlines -> Inlines) -> Maybe (Inlines -> Inlines))
-> (Inlines -> Inlines) -> Maybe (Inlines -> Inlines)
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines)
-> Maybe (Inlines -> Inlines) -> Inlines -> Inlines
forall {b} {c}. (b -> c) -> Maybe (b -> b) -> b -> c
wrapInConstr Inlines -> Inlines
B.underline Maybe (Inlines -> Inlines)
accConstr, [a]
other)
a
"underline" -> ((Inlines -> Inlines) -> Maybe (Inlines -> Inlines)
forall a. a -> Maybe a
Just ((Inlines -> Inlines) -> Maybe (Inlines -> Inlines))
-> (Inlines -> Inlines) -> Maybe (Inlines -> Inlines)
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines)
-> Maybe (Inlines -> Inlines) -> Inlines -> Inlines
forall {b} {c}. (b -> c) -> Maybe (b -> b) -> b -> c
wrapInConstr Inlines -> Inlines
B.underline Maybe (Inlines -> Inlines)
accConstr, [a]
other)
a
_ -> (Maybe (Inlines -> Inlines)
accConstr, a
clsa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
other)
in case (Text
ident, [Text]
remainingClasses, [Target]
kvs') of
(Text
"", [], []) -> (Inlines -> Inlines)
-> Maybe (Inlines -> Inlines) -> Inlines -> Inlines
forall a. a -> Maybe a -> a
fromMaybe (Attr -> Inlines -> Inlines
B.spanWith Attr
nullAttr) Maybe (Inlines -> Inlines)
mConstr
Attr
attr -> (Inlines -> Inlines)
-> Maybe (Inlines -> Inlines) -> Inlines -> Inlines
forall {b} {c}. (b -> c) -> Maybe (b -> b) -> b -> c
wrapInConstr (Attr -> Inlines -> Inlines
B.spanWith Attr
attr) Maybe (Inlines -> Inlines)
mConstr
isSmallCapsFontVariant :: Text -> Bool
isSmallCapsFontVariant :: Text -> Bool
isSmallCapsFontVariant Text
s =
Text -> Text
T.toLower ((Char -> Bool) -> Text -> Text
T.filter (Char -> FilePath -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Char
' ', Char
'\t', Char
';']) Text
s) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==
Text
"font-variant:small-caps"
regLink :: PandocMonad m
=> (Attr -> Text -> Text -> Inlines -> Inlines)
-> F Inlines
-> MarkdownParser m (F Inlines)
regLink :: forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> F Inlines -> MarkdownParser m (F Inlines)
regLink Attr -> Text -> Text -> Inlines -> Inlines
constructor F Inlines
lab = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
(!Text
src, !Text
tit) <- MarkdownParser m Target
forall (m :: * -> *). PandocMonad m => MarkdownParser m Target
source
Bool
rebase <- Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (Bool
True Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_rebase_relative_paths)
SourcePos
pos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
let !src' :: Text
src' = if Bool
rebase then SourcePos -> Text -> Text
rebasePath SourcePos
pos Text
src else Text
src
!Attr
attr <- Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState 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 Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_link_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> ParsecT Sources ParserState m (F Inlines))
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
constructor Attr
attr Text
src' Text
tit (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
lab
referenceLink :: PandocMonad m
=> (Attr -> Text -> Text -> Inlines -> Inlines)
-> (F Inlines, Text)
-> MarkdownParser m (F Inlines)
referenceLink :: forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> (F Inlines, Text) -> MarkdownParser m (F Inlines)
referenceLink Attr -> Text -> Text -> Inlines -> Inlines
constructor (F Inlines
lab, Text
raw) = do
Bool
sp <- (Bool
True Bool
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState 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 ParserState 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 ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
(F Inlines
_,!Text
raw') <- (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (F Inlines
forall a. Monoid a => a
mempty, Text
"") (ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text))
-> ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall a b. (a -> b) -> a -> b
$
ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_citations
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_spaced_reference_links ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl
MarkdownParser m (F [Citation])
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Citation])
normalCite
(F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
forall a. Monoid a => a
mempty, Text
"")))
ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ((Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardDisabled Extension
Ext_spaced_reference_links ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m (F Inlines, Text)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference)
Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
raw' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"") (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_shortcut_reference_links
!Attr
attr <- Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState 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 Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_link_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes
let !labIsRef :: Bool
labIsRef = Text
raw' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"" Bool -> Bool -> Bool
|| Text
raw' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"[]"
let (Bool
exclam, Text
rawsuffix) =
case Text -> Maybe (Char, Text)
T.uncons Text
raw of
Just (Char
'!', Text
rest) -> (Bool
True, Text
rest)
Maybe (Char, Text)
_ -> (Bool
False, Text
raw)
let !key :: Key
key = Text -> Key
toKey (Text -> Key) -> Text -> Key
forall a b. (a -> b) -> a -> b
$ if Bool
labIsRef then Text
rawsuffix else Text
raw'
F Inlines
parsedRaw <- MarkdownParser m (F Inlines)
-> Text -> MarkdownParser m (F Inlines)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines Text
raw'
F Inlines
fallback <- MarkdownParser m (F Inlines)
-> Text -> MarkdownParser m (F Inlines)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines (Text -> MarkdownParser m (F Inlines))
-> Text -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ if Bool
exclam
then Text
rawsuffix
else Text -> Text
dropBrackets Text
rawsuffix
Bool
implicitHeaderRefs <- Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool)
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall a b. (a -> b) -> a -> b
$
Bool
True Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_implicit_header_references
let makeFallback :: F Inlines
makeFallback = do
Inlines
parsedRaw' <- F Inlines
parsedRaw
Inlines
fallback' <- F Inlines
fallback
Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ (if Bool
exclam
then Inlines
"!" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
fallback'
else Text -> Inlines
B.str Text
"[" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
fallback' Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
B.str Text
"]") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
(if Bool
sp Bool -> Bool -> Bool
&& Bool -> Bool
not (Text -> Bool
T.null Text
raw) then Inlines
B.space else Inlines
forall a. Monoid a => a
mempty) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
Inlines
parsedRaw'
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
KeyTable
keys <- (ParserState -> KeyTable) -> Future ParserState KeyTable
forall s a. (s -> a) -> Future s a
asksF ParserState -> KeyTable
stateKeys
case Key -> KeyTable -> Maybe (Target, Attr)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Key
key KeyTable
keys of
Maybe (Target, Attr)
Nothing ->
if Bool
implicitHeaderRefs
then do
KeyTable
headerKeys <- (ParserState -> KeyTable) -> Future ParserState KeyTable
forall s a. (s -> a) -> Future s a
asksF ParserState -> KeyTable
stateHeaderKeys
case Key -> KeyTable -> Maybe (Target, Attr)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Key
key KeyTable
headerKeys of
Just ((Text
src, Text
tit), Attr
_) -> Attr -> Text -> Text -> Inlines -> Inlines
constructor Attr
attr Text
src Text
tit (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
lab
Maybe (Target, Attr)
Nothing -> F Inlines
makeFallback
else F Inlines
makeFallback
Just ((Text
src,Text
tit), Attr
defattr) ->
Attr -> Text -> Text -> Inlines -> Inlines
constructor (Attr -> Attr -> Attr
combineAttr Attr
attr Attr
defattr) Text
src Text
tit (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
lab
dropBrackets :: Text -> Text
dropBrackets :: Text -> Text
dropBrackets = Text -> Text
dropRB (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
dropLB
where dropRB :: Text -> Text
dropRB (Text -> Maybe (Text, Char)
T.unsnoc -> Just (Text
xs,Char
']')) = Text
xs
dropRB Text
xs = Text
xs
dropLB :: Text -> Text
dropLB (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'[',Text
xs)) = Text
xs
dropLB Text
xs = Text
xs
bareURL :: PandocMonad m => MarkdownParser m (F Inlines)
bareURL :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
bareURL = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_autolink_bare_uris
ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState ParsecT Sources ParserState m ParserState
-> (ParserState -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> (ParserState -> Bool)
-> ParserState
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserState -> Bool
stateAllowLinks
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
(Text
cls, (Text
orig, Text
src)) <- ((Text
"uri",) (Target -> (Text, Target))
-> ParsecT Sources ParserState m Target
-> ParsecT Sources ParserState m (Text, Target)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Target
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Target
uri) ParsecT Sources ParserState m (Text, Target)
-> ParsecT Sources ParserState m (Text, Target)
-> ParsecT Sources ParserState m (Text, Target)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((Text
"email",) (Target -> (Text, Target))
-> ParsecT Sources ParserState m Target
-> ParsecT Sources ParserState m (Text, Target)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Target
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Target
emailAddress)
ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text, Text))
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose (Text
"a" :: Text))
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
B.linkWith (Text
"",[Text
cls],[]) Text
src Text
"" (Text -> Inlines
B.str Text
orig)
autoLink :: PandocMonad m => MarkdownParser m (F Inlines)
autoLink :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
autoLink = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState ParsecT Sources ParserState m ParserState
-> (ParserState -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> (ParserState -> Bool)
-> ParserState
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserState -> Bool
stateAllowLinks
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<'
(Text
cls, (Text
orig, Text
src)) <- ((Text
"uri",) (Target -> (Text, Target))
-> ParsecT Sources ParserState m Target
-> ParsecT Sources ParserState m (Text, Target)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Target
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Target
uri) ParsecT Sources ParserState m (Text, Target)
-> ParsecT Sources ParserState m (Text, Target)
-> ParsecT Sources ParserState m (Text, Target)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((Text
"email",) (Target -> (Text, Target))
-> ParsecT Sources ParserState m Target
-> ParsecT Sources ParserState m (Text, Target)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Target
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Target
emailAddress)
Text
extra <- Text -> Text
fromEntities (Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>')
Attr
attr <- Attr
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Text
"", [Text
cls], []) (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_link_attributes ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> ParsecT Sources ParserState m (F Inlines))
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
B.linkWith Attr
attr (Text
src Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeURI Text
extra) Text
""
(Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
orig Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
extra)
rebasePath :: SourcePos -> Text -> Text
rebasePath :: SourcePos -> Text -> Text
rebasePath SourcePos
pos Text
path = do
let fp :: FilePath
fp = SourcePos -> FilePath
sourceName SourcePos
pos
isFragment :: Bool
isFragment = Int -> Text -> Text
T.take Int
1 Text
path Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"#"
path' :: FilePath
path' = Text -> FilePath
T.unpack Text
path
isAbsolutePath :: Bool
isAbsolutePath = FilePath -> Bool
Posix.isAbsolute FilePath
path' Bool -> Bool -> Bool
|| FilePath -> Bool
Windows.isAbsolute FilePath
path'
in if Text -> Bool
T.null Text
path Bool -> Bool -> Bool
|| Bool
isFragment Bool -> Bool -> Bool
|| Bool
isAbsolutePath Bool -> Bool -> Bool
|| Text -> Bool
isURI Text
path
then Text
path
else
case FilePath -> FilePath
takeDirectory FilePath
fp of
FilePath
"" -> Text
path
FilePath
"." -> Text
path
FilePath
d -> FilePath -> Text
T.pack FilePath
d Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
path
image :: PandocMonad m => MarkdownParser m (F Inlines)
image :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
image = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'!'
(Attr -> Text -> Text -> Inlines -> Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> MarkdownParser m (F Inlines)
wikilink Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
do (F Inlines
lab,Text
raw) <- MarkdownParser m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference
Text
defaultExt <- (ReaderOptions -> Text) -> ParsecT Sources ParserState m Text
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 ParserState m b
getOption ReaderOptions -> Text
readerDefaultImageExtension
let constructor :: Attr -> Text -> Text -> Inlines -> Inlines
constructor Attr
attr' Text
src
| Text
"data:" Text -> Text -> Bool
`T.isPrefixOf` Text
src = Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith Attr
attr' Text
src
| Bool
otherwise =
case FilePath -> FilePath
takeExtension (Text -> FilePath
T.unpack Text
src) of
FilePath
"" -> Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith Attr
attr' (FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> FilePath
addExtension (Text -> FilePath
T.unpack Text
src)
(FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Text -> FilePath
T.unpack Text
defaultExt)
FilePath
_ -> Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith Attr
attr' Text
src
(Attr -> Text -> Text -> Inlines -> Inlines)
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> F Inlines -> MarkdownParser m (F Inlines)
regLink Attr -> Text -> Text -> Inlines -> Inlines
constructor F Inlines
lab ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Attr -> Text -> Text -> Inlines -> Inlines)
-> (F Inlines, Text) -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> (F Inlines, Text) -> MarkdownParser m (F Inlines)
referenceLink Attr -> Text -> Text -> Inlines -> Inlines
constructor (F Inlines
lab, Text
"!" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
raw)
note :: PandocMonad m => MarkdownParser m (F Inlines)
note :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
note = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_footnotes
Text
ref <- MarkdownParser m Text
forall (m :: * -> *). PandocMonad m => MarkdownParser m Text
noteMarker
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateNoteRefs = Set.insert ref (stateNoteRefs st)
, stateNoteNumber = stateNoteNumber st + 1 }
Int
noteNum <- ParserState -> Int
stateNoteNumber (ParserState -> Int)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> ParsecT Sources ParserState m (F Inlines))
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Map Text (SourcePos, Future ParserState Blocks)
notes <- (ParserState -> Map Text (SourcePos, Future ParserState Blocks))
-> Future
ParserState (Map Text (SourcePos, Future ParserState Blocks))
forall s a. (s -> a) -> Future s a
asksF ParserState -> Map Text (SourcePos, Future ParserState Blocks)
stateNotes'
case Text
-> Map Text (SourcePos, Future ParserState Blocks)
-> Maybe (SourcePos, Future ParserState Blocks)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
ref Map Text (SourcePos, Future ParserState Blocks)
notes of
Maybe (SourcePos, Future ParserState Blocks)
Nothing -> Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
"[^" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ref Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
Just (SourcePos
_pos, Future ParserState Blocks
contents) -> do
ParserState
st <- Future ParserState ParserState
forall s. Future s s
askF
let contents' :: Blocks
contents' = Future ParserState Blocks -> ParserState -> Blocks
forall s a. Future s a -> s -> a
runF Future ParserState Blocks
contents ParserState
st{ stateNotes' = M.empty }
let addCitationNoteNum :: Citation -> Citation
addCitationNoteNum c :: Citation
c@Citation{} =
Citation
c{ citationNoteNum = noteNum }
let adjustCite :: Inline -> Inline
adjustCite (Cite [Citation]
cs [Inline]
ils) =
[Citation] -> [Inline] -> Inline
Cite ((Citation -> Citation) -> [Citation] -> [Citation]
forall a b. (a -> b) -> [a] -> [b]
map Citation -> Citation
addCitationNoteNum [Citation]
cs) [Inline]
ils
adjustCite Inline
x = Inline
x
Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Blocks -> Inlines
B.note (Blocks -> Inlines) -> Blocks -> Inlines
forall a b. (a -> b) -> a -> b
$ (Inline -> Inline) -> Blocks -> Blocks
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
adjustCite Blocks
contents'
inlineNote :: PandocMonad m => MarkdownParser m (F Inlines)
inlineNote :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlineNote = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_inline_notes
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'^'
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateInNote = True
, stateNoteNumber = stateNoteNumber st + 1 }
F Inlines
contents <- MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall (m :: * -> *) a.
PandocMonad m =>
MarkdownParser m (F a) -> MarkdownParser m (F a)
inBalancedBrackets MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateInNote = False }
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Blocks -> Inlines
B.note (Blocks -> Inlines) -> (Inlines -> Blocks) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Blocks
B.para (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
contents
rawLaTeXInline' :: PandocMonad m => MarkdownParser m (F Inlines)
rawLaTeXInline' :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
rawLaTeXInline' = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_tex
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ParsecT Sources ParserState m Text
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Text
rawConTeXtEnvironment
!Text
s <- ParsecT Sources ParserState m Text
forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
ParsecT Sources s m Text
rawLaTeXInline
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines
B.rawInline Text
"tex" Text
s
rawConTeXtEnvironment :: PandocMonad m => ParsecT Sources st m Text
rawConTeXtEnvironment :: forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Text
rawConTeXtEnvironment = 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
FilePath -> ParsecT Sources st m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"\\start"
Text
completion <- ParsecT Sources st m Char -> ParsecT Sources st m Text
forall (m :: * -> *) st.
PandocMonad m =>
ParsecT Sources st m Char -> ParsecT Sources st m Text
inBrackets (ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter ParsecT Sources st m Char
-> ParsecT Sources st m Char -> ParsecT Sources st m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit ParsecT Sources st m Char
-> ParsecT Sources st m Char -> ParsecT Sources st m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar)
ParsecT Sources st m Text
-> 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 -> ParsecT s u m a
<|> ParsecT Sources st m Char -> ParsecT Sources st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter
![Text]
contents <- ParsecT Sources st m Text
-> ParsecT Sources st m Text -> ParsecT Sources st m [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill (ParsecT Sources st m Text
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m Text
rawConTeXtEnvironment ParsecT Sources st m Text
-> 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 -> ParsecT s u m a
<|> Int -> ParsecT Sources st m Char -> ParsecT Sources st m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar)
(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
$ FilePath -> ParsecT Sources st m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
"\\stop" ParsecT Sources st m FilePath
-> ParsecT Sources st m Text -> ParsecT Sources st m Text
forall a b.
ParsecT Sources st m a
-> ParsecT Sources st m b -> ParsecT Sources st m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> ParsecT Sources st m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
completion)
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
"\\start" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
completion Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.concat [Text]
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\\stop" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
completion
inBrackets :: PandocMonad m => ParsecT Sources st m Char -> ParsecT Sources st m Text
inBrackets :: forall (m :: * -> *) st.
PandocMonad m =>
ParsecT Sources st m Char -> ParsecT Sources st m Text
inBrackets ParsecT Sources st m Char
parser = do
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
'['
Text
contents <- ParsecT Sources st m Char -> ParsecT Sources st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar ParsecT Sources st m Char
parser
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
']'
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
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
spanHtml :: PandocMonad m => MarkdownParser m (F Inlines)
spanHtml :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
spanHtml = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_native_spans
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
(TagOpen Text
_ [Target]
attrs, Text
_) <- (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Target] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen (Text
"span" :: Text) [])
F Inlines
contents <- [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m [F Inlines]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose (Text
"span" :: Text)))
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 -> [Target] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [Target]
attrs
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 -> [Target] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Target]
attrs
let keyvals :: [Target]
keyvals = [(Text
k,Text
v) | (Text
k,Text
v) <- [Target]
attrs, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"id" Bool -> Bool -> Bool
&& Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"class"]
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
wrapSpan (Text
ident, [Text]
classes, [Target]
keyvals) (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
contents
divHtml :: PandocMonad m => MarkdownParser m (F Blocks)
divHtml :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
divHtml = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_native_divs
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks))
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
SourcePos
openpos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
(TagOpen Text
_ [Target]
attrs, Text
_) <- (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Target] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen (Text
"div" :: Text) [])
Maybe Text
oldInHtmlBlock <- ParserState -> Maybe Text
stateInHtmlBlock (ParserState -> Maybe Text)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateInHtmlBlock = Just "div" }
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Future ParserState Blocks
contents <- [Future ParserState Blocks] -> Future ParserState Blocks
forall a. Monoid a => [a] -> a
mconcat ([Future ParserState Blocks] -> Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> MarkdownParser m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
MarkdownParser m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose (Text
"div" :: Text)))
ParsecT Sources ParserState m ()
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
block)
ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose (Text
"div" :: Text))) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition ParsecT Sources ParserState m SourcePos
-> (SourcePos -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= LogMessage -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT Sources ParserState m ())
-> (SourcePos -> LogMessage)
-> SourcePos
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourcePos -> SourcePos -> LogMessage
UnclosedDiv SourcePos
openpos)
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 -> [Target] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [Target]
attrs
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 -> [Target] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Target]
attrs
let keyvals :: [Target]
keyvals = [(Text
k,Text
v) | (Text
k,Text
v) <- [Target]
attrs, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"id" Bool -> Bool -> Bool
&& Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"class"]
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateInHtmlBlock = oldInHtmlBlock }
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith (Text
ident, [Text]
classes, [Target]
keyvals) (Blocks -> Blocks)
-> Future ParserState Blocks -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future ParserState Blocks
contents
divFenced :: PandocMonad m => MarkdownParser m (F Blocks)
divFenced :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
divFenced = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_fenced_divs
MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks))
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ do
SourcePos
openpos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
":::"
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Attr
attribs <- MarkdownParser m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes MarkdownParser m Attr
-> MarkdownParser m Attr -> MarkdownParser m Attr
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((\Text
x -> (Text
"",[Text
x],[])) (Text -> Attr)
-> ParsecT Sources ParserState m Text -> MarkdownParser m Attr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar)
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (Char -> ParsecT Sources ParserState 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 ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st ->
ParserState
st{ stateFencedDivLevel = stateFencedDivLevel st + 1 }
Future ParserState Blocks
bs <- [Future ParserState Blocks] -> Future ParserState Blocks
forall a. Monoid a => [a] -> a
mconcat ([Future ParserState Blocks] -> Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
-> MarkdownParser m (Future ParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MarkdownParser m (Future ParserState Blocks)
-> ParsecT Sources ParserState m [Future ParserState Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
divFenceEnd ParsecT Sources ParserState m ()
-> MarkdownParser m (Future ParserState Blocks)
-> MarkdownParser m (Future ParserState Blocks)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MarkdownParser m (Future ParserState Blocks)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Blocks)
block)
ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
divFenceEnd ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition ParsecT Sources ParserState m SourcePos
-> (SourcePos -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= LogMessage -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT Sources ParserState m ())
-> (SourcePos -> LogMessage)
-> SourcePos
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourcePos -> SourcePos -> LogMessage
UnclosedDiv SourcePos
openpos)
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st ->
ParserState
st{ stateFencedDivLevel = stateFencedDivLevel st - 1 }
Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks))
-> Future ParserState Blocks
-> MarkdownParser m (Future ParserState Blocks)
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
B.divWith Attr
attribs (Blocks -> Blocks)
-> Future ParserState Blocks -> Future ParserState Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future ParserState Blocks
bs
divFenceEnd :: PandocMonad m => MarkdownParser m ()
divFenceEnd :: forall (m :: * -> *). PandocMonad m => MarkdownParser m ()
divFenceEnd = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ do
FilePath -> ParsecT Sources ParserState m FilePath
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m FilePath
string FilePath
":::"
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (Char -> ParsecT Sources ParserState 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 ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
() -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
rawHtmlInline :: PandocMonad m => MarkdownParser m (F Inlines)
rawHtmlInline :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
rawHtmlInline = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_html
Maybe Text
inHtmlBlock <- ParserState -> Maybe Text
stateInHtmlBlock (ParserState -> Maybe Text)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let isCloseBlockTag :: Tag str -> Bool
isCloseBlockTag Tag str
t = case Maybe Text
inHtmlBlock of
Just Text
t' -> Tag str
t Tag str -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose Text
t'
Maybe Text
Nothing -> Bool
False
Bool
mdInHtml <- Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool)
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall a b. (a -> b) -> a -> b
$
( Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_markdown_in_html_blocks
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_markdown_attribute
) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
(Tag Text
_,Text
result) <- (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text))
-> (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall a b. (a -> b) -> a -> b
$ if Bool
mdInHtml
then (\Tag Text
x -> Tag Text -> Bool
isInlineTag Tag Text
x Bool -> Bool -> Bool
&&
Bool -> Bool
not (Tag Text -> Bool
forall {str}. StringLike str => Tag str -> Bool
isCloseBlockTag Tag Text
x))
else Bool -> Bool
not (Bool -> Bool) -> (Tag Text -> Bool) -> Tag Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tag Text -> Bool
isTextTag
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines
B.rawInline Text
"html" Text
result
emoji :: PandocMonad m => MarkdownParser m (F Inlines)
emoji :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
emoji = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_emoji
MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':'
Text
emojikey <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
"_+-")
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':'
case Text -> Maybe Inline
emojiToInline Text
emojikey of
Just Inline
i -> F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Inline -> Inlines
forall a. a -> Many a
B.singleton Inline
i)
Maybe Inline
Nothing -> MarkdownParser m (F Inlines)
forall a. ParsecT Sources ParserState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
cite :: PandocMonad m => MarkdownParser m (F Inlines)
cite :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
cite = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_citations
Bool
inNote <- ParserState -> Bool
stateInNote (ParserState -> Bool)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
inNote (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateNoteNumber = stateNoteNumber st + 1 }
MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
textualCite
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> do (F [Citation]
cs, Text
raw) <- ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation], Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw ParsecT Sources ParserState m (F [Citation])
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Citation])
normalCite
F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> MarkdownParser m (F Inlines))
-> F Inlines -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ ([Citation] -> Inlines -> Inlines)
-> Inlines -> [Citation] -> Inlines
forall a b c. (a -> b -> c) -> b -> a -> c
flip [Citation] -> Inlines -> Inlines
B.cite (Text -> Inlines
B.text Text
raw) ([Citation] -> Inlines) -> F [Citation] -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F [Citation]
cs
textualCite :: PandocMonad m => MarkdownParser m (F Inlines)
textualCite :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
textualCite = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
(Bool
suppressAuthor, Text
key) <- Bool -> ParsecT Sources ParserState m (Bool, Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, HasLastStrPosition st) =>
Bool -> ParsecT s st m (Bool, Text)
citeKey Bool
True
ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState ParsecT Sources ParserState m ParserState
-> (ParserState -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> (ParserState -> Bool)
-> ParserState
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Int -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe Int -> Bool)
-> (ParserState -> Maybe Int) -> ParserState -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Map Text Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
key (Map Text Int -> Maybe Int)
-> (ParserState -> Map Text Int) -> ParserState -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParserState -> Map Text Int
stateExamples
Int
noteNum <- ParserState -> Int
stateNoteNumber (ParserState -> Int)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let first :: Citation
first = Citation{ citationId :: Text
citationId = Text
key
, citationPrefix :: [Inline]
citationPrefix = []
, citationSuffix :: [Inline]
citationSuffix = []
, citationMode :: CitationMode
citationMode = if Bool
suppressAuthor
then CitationMode
SuppressAuthor
else CitationMode
AuthorInText
, citationNoteNum :: Int
citationNoteNum = Int
noteNum
, citationHash :: Int
citationHash = Int
0
}
(do
(F [Citation]
cs, Text
raw) <- ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation], Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw (ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation], Text))
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation], Text)
forall a b. (a -> b) -> a -> b
$
(([Citation] -> [Citation]) -> F [Citation] -> F [Citation]
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Citation
firstCitation -> [Citation] -> [Citation]
forall a. a -> [a] -> [a]
:) (F [Citation] -> F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m (F [Citation])
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Citation])
normalCite))
ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Citation -> ParsecT Sources ParserState m (F [Citation])
forall (m :: * -> *).
PandocMonad m =>
Citation -> MarkdownParser m (F [Citation])
bareloc Citation
first
let (Text
spaces',Text
raw') = (Char -> Bool) -> Text -> Target
T.span Char -> Bool
isSpace Text
raw
spc :: Inlines
spc | Text -> Bool
T.null Text
spaces' = Inlines
forall a. Monoid a => a
mempty
| Bool
otherwise = Inlines
B.space
F Inlines
lab <- ParsecT Sources ParserState m (F Inlines)
-> Text -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inlines (Text -> ParsecT Sources ParserState m (F Inlines))
-> Text -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ Text -> Text
dropBrackets Text
raw'
F Inlines
fallback <- (Attr -> Text -> Text -> Inlines -> Inlines)
-> (F Inlines, Text) -> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
(Attr -> Text -> Text -> Inlines -> Inlines)
-> (F Inlines, Text) -> MarkdownParser m (F Inlines)
referenceLink Attr -> Text -> Text -> Inlines -> Inlines
B.linkWith (F Inlines
lab,Text
raw')
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateNoteNumber = noteNum }
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> ParsecT Sources ParserState m (F Inlines))
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Inlines
fallback' <- F Inlines
fallback
[Citation]
cs' <- F [Citation]
cs
Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$
case Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
fallback' of
Link{}:[Inline]
_ -> [Citation] -> Inlines -> Inlines
B.cite [Citation
first] (Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
"@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
spc Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
fallback'
[Inline]
_ -> [Citation] -> Inlines -> Inlines
B.cite [Citation]
cs' (Text -> Inlines
B.text (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
"@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
raw))
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (do ParserState
st <- Future ParserState ParserState
forall s. Future s s
askF
Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ case Text -> Map Text Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
key (ParserState -> Map Text Int
stateExamples ParserState
st) of
Just Int
n -> Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. Show a => a -> Text
tshow Int
n
Maybe Int
_ -> [Citation] -> Inlines -> Inlines
B.cite [Citation
first] (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
"@" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key)
bareloc :: PandocMonad m => Citation -> MarkdownParser m (F [Citation])
bareloc :: forall (m :: * -> *).
PandocMonad m =>
Citation -> MarkdownParser m (F [Citation])
bareloc Citation
c = ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation]))
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'^'
F Inlines
suff <- MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
suffix
F [Citation]
rest <- F [Citation]
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option ([Citation] -> F [Citation]
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return []) (ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation]))
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation]))
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F [Citation])
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Citation])
citeList
ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl
Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
"[("
F [Citation] -> ParsecT Sources ParserState m (F [Citation])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F [Citation] -> ParsecT Sources ParserState m (F [Citation]))
-> F [Citation] -> ParsecT Sources ParserState m (F [Citation])
forall a b. (a -> b) -> a -> b
$ do
Inlines
suff' <- F Inlines
suff
[Citation]
rest' <- F [Citation]
rest
[Citation] -> F [Citation]
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Citation] -> F [Citation]) -> [Citation] -> F [Citation]
forall a b. (a -> b) -> a -> b
$ Citation
c{ citationSuffix = B.toList suff' } Citation -> [Citation] -> [Citation]
forall a. a -> [a] -> [a]
: [Citation]
rest'
normalCite :: PandocMonad m => MarkdownParser m (F [Citation])
normalCite :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Citation])
normalCite = ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation]))
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall a b. (a -> b) -> a -> b
$ do
F [Citation]
citations <- ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall (m :: * -> *) a.
PandocMonad m =>
MarkdownParser m (F a) -> MarkdownParser m (F a)
inBalancedBrackets (ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m (F [Citation])
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m (F [Citation])
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Citation])
citeList ParsecT Sources ParserState m (F [Citation])
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F [Citation])
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl)
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Target
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources ParserState m Target
forall (m :: * -> *). PandocMonad m => MarkdownParser m Target
source) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_bracketed_spans ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => MarkdownParser m Attr
attributes) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m (F Inlines, Text)
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources ParserState m (F Inlines, Text)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F Inlines, Text)
reference)
F [Citation] -> ParsecT Sources ParserState m (F [Citation])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return F [Citation]
citations
suffix :: PandocMonad m => MarkdownParser m (F Inlines)
suffix :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
suffix = ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines))
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Bool
hasSpace <- Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True)
ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl
[F Inlines]
ils <- ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (FilePath -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
FilePath -> ParsecT s u m Char
oneOf FilePath
";]") ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline)
let rest :: F Inlines
rest = F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF ([F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat [F Inlines]
ils)
F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> ParsecT Sources ParserState m (F Inlines))
-> F Inlines -> ParsecT Sources ParserState m (F Inlines)
forall a b. (a -> b) -> a -> b
$ if Bool
hasSpace Bool -> Bool -> Bool
&& Bool -> Bool
not ([F Inlines] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [F Inlines]
ils)
then (Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>) (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
rest
else F Inlines
rest
prefix :: PandocMonad m => MarkdownParser m (F Inlines)
prefix :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
prefix = F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> ParsecT Sources ParserState m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [F Inlines]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> ParsecT Sources ParserState 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 ParserState m ()
-> ParsecT Sources ParserState m (F Inlines)
-> ParsecT Sources ParserState m (F Inlines)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline) (Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead
(ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ do ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl))
Bool -> ParsecT Sources ParserState m (Bool, Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, HasLastStrPosition st) =>
Bool -> ParsecT s st m (Bool, Text)
citeKey Bool
True
Char -> ParsecT Sources ParserState m Char
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Char
']'))
citeList :: PandocMonad m => MarkdownParser m (F [Citation])
citeList :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (F [Citation])
citeList = ([Future ParserState Citation] -> F [Citation])
-> ParsecT Sources ParserState m [Future ParserState Citation]
-> ParsecT Sources ParserState m (F [Citation])
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Future ParserState Citation] -> F [Citation]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence (ParsecT Sources ParserState m [Future ParserState Citation]
-> ParsecT Sources ParserState m (F [Citation]))
-> ParsecT Sources ParserState m [Future ParserState Citation]
-> ParsecT Sources ParserState m (F [Citation])
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (Future ParserState Citation)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Future ParserState Citation]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy1 ParsecT Sources ParserState m (Future ParserState Citation)
forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Citation)
citation (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState 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 ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall (m :: * -> *) st. PandocMonad m => ParsecT Sources st m ()
spnl)
citation :: PandocMonad m => MarkdownParser m (F Citation)
citation :: forall (m :: * -> *).
PandocMonad m =>
MarkdownParser m (Future ParserState Citation)
citation = ParsecT Sources ParserState m (Future ParserState Citation)
-> ParsecT Sources ParserState m (Future ParserState Citation)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Future ParserState Citation)
-> ParsecT Sources ParserState m (Future ParserState Citation))
-> ParsecT Sources ParserState m (Future ParserState Citation)
-> ParsecT Sources ParserState m (Future ParserState Citation)
forall a b. (a -> b) -> a -> b
$ do
F Inlines
pref <- MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
prefix
(Bool
suppress_author, Text
key) <- Bool -> ParsecT Sources ParserState m (Bool, Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, HasLastStrPosition st) =>
Bool -> ParsecT s st m (Bool, Text)
citeKey Bool
True
F Inlines
suff <- MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
suffix
Int
noteNum <- ParserState -> Int
stateNoteNumber (ParserState -> Int)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Future ParserState Citation
-> ParsecT Sources ParserState m (Future ParserState Citation)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future ParserState Citation
-> ParsecT Sources ParserState m (Future ParserState Citation))
-> Future ParserState Citation
-> ParsecT Sources ParserState m (Future ParserState Citation)
forall a b. (a -> b) -> a -> b
$ do
Inlines
x <- F Inlines
pref
Inlines
y <- F Inlines
suff
Citation -> Future ParserState Citation
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Citation{ citationId :: Text
citationId = Text
key
, citationPrefix :: [Inline]
citationPrefix = Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
x
, citationSuffix :: [Inline]
citationSuffix = Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
y
, citationMode :: CitationMode
citationMode = if Bool
suppress_author
then CitationMode
SuppressAuthor
else CitationMode
NormalCitation
, citationNoteNum :: Int
citationNoteNum = Int
noteNum
, citationHash :: Int
citationHash = Int
0
}
smart :: PandocMonad m => MarkdownParser m (F Inlines)
smart :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
smart = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_smart
MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
doubleQuoted MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
singleQuoted MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> ParsecT Sources ParserState m Inlines
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines
doubleCloseQuote) MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> ParsecT Sources ParserState m Inlines
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines
apostrophe) MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> ParsecT Sources ParserState m Inlines
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
forall st s (m :: * -> *).
(HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines
dash) MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> ParsecT Sources ParserState m Inlines
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines
ellipses)
singleQuoted :: PandocMonad m => MarkdownParser m (F Inlines)
singleQuoted :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
singleQuoted = do
ParsecT Sources ParserState m ()
forall st (m :: * -> *) s.
(HasLastStrPosition st, HasQuoteContext st m, Stream s m Char,
UpdateSourcePos s Char) =>
ParsecT s st m ()
singleQuoteStart
(MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (QuoteContext
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s a.
QuoteContext
-> ParsecT s ParserState m a -> ParsecT s ParserState m a
forall st (m :: * -> *) s a.
HasQuoteContext st m =>
QuoteContext -> ParsecT s st m a -> ParsecT s st m a
withQuoteContext QuoteContext
InSingleQuote (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$
(Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.singleQuoted (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [F Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
singleQuoteEnd))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
B.str Text
"\8217")))
doubleQuoted :: PandocMonad m => MarkdownParser m (F Inlines)
doubleQuoted :: forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
doubleQuoted = do
ParsecT Sources ParserState m ()
forall st (m :: * -> *) s.
(HasLastStrPosition st, HasQuoteContext st m, Stream s m Char,
UpdateSourcePos s Char) =>
ParsecT s st m ()
doubleQuoteStart
(MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (QuoteContext
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s a.
QuoteContext
-> ParsecT s ParserState m a -> ParsecT s ParserState m a
forall st (m :: * -> *) s a.
HasQuoteContext st m =>
QuoteContext -> ParsecT s st m a -> ParsecT s st m a
withQuoteContext QuoteContext
InDoubleQuote (MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines))
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$
(Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future ParserState a -> Future ParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.doubleQuoted (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT Sources ParserState m [F Inlines]
-> MarkdownParser m (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
MarkdownParser m (F Inlines)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [F Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till MarkdownParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => MarkdownParser m (F Inlines)
inline ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
doubleQuoteEnd))
MarkdownParser m (F Inlines)
-> MarkdownParser m (F Inlines) -> MarkdownParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (F Inlines -> MarkdownParser m (F Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines
forall a. a -> Future ParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
B.str Text
"\8220")))