{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Readers.MediaWiki
   Copyright   : Copyright (C) 2012-2022 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Conversion of mediawiki text to 'Pandoc' document.
-}
{-
TODO:
_ correctly handle tables within tables
_ parse templates?
-}
module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where

import Control.Monad
import Control.Monad.Except (throwError)
import Data.Char (isDigit, isSpace)
import qualified Data.Foldable as F
import Data.List (intersperse)
import Data.Maybe (fromMaybe, maybeToList)
import Data.Sequence (ViewL (..), viewl, (<|))
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import Text.HTML.TagSoup
import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.Definition
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (nested)
import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isCommentTag)
import Text.Pandoc.Shared (safeRead, stringify, stripTrailingNewlines,
                           trim, splitTextBy, tshow)
import Text.Pandoc.Walk (walk)
import Text.Pandoc.XML (fromEntities)

-- | Read mediawiki from an input string and return a Pandoc document.
readMediaWiki :: (PandocMonad m, ToSources a)
              => ReaderOptions
              -> a
              -> m Pandoc
readMediaWiki :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readMediaWiki ReaderOptions
opts a
s = do
  let sources :: Sources
sources = a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s
  Either PandocError Pandoc
parsed <- ParserT Sources MWState m Pandoc
-> MWState -> Sources -> m (Either PandocError Pandoc)
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParserT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParserT Sources MWState m Pandoc
forall (m :: * -> *). PandocMonad m => MWParser m Pandoc
parseMediaWiki MWState :: ReaderOptions
-> Int
-> Int
-> [Many Inline]
-> Set Text
-> [LogMessage]
-> Bool
-> MWState
MWState{ mwOptions :: ReaderOptions
mwOptions = ReaderOptions
opts
                                            , mwMaxNestingLevel :: Int
mwMaxNestingLevel = Int
4
                                            , mwNextLinkNumber :: Int
mwNextLinkNumber  = Int
1
                                            , mwCategoryLinks :: [Many Inline]
mwCategoryLinks = []
                                            , mwIdentifierList :: Set Text
mwIdentifierList = Set Text
forall a. Set a
Set.empty
                                            , mwLogMessages :: [LogMessage]
mwLogMessages = []
                                            , mwInTT :: Bool
mwInTT = Bool
False
                                            }
            Sources
sources
  case Either PandocError Pandoc
parsed of
    Right Pandoc
result -> Pandoc -> m Pandoc
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
result
    Left PandocError
e       -> PandocError -> m Pandoc
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e

data MWState = MWState { MWState -> ReaderOptions
mwOptions         :: ReaderOptions
                       , MWState -> Int
mwMaxNestingLevel :: Int
                       , MWState -> Int
mwNextLinkNumber  :: Int
                       , MWState -> [Many Inline]
mwCategoryLinks   :: [Inlines]
                       , MWState -> Set Text
mwIdentifierList  :: Set.Set Text
                       , MWState -> [LogMessage]
mwLogMessages     :: [LogMessage]
                       , MWState -> Bool
mwInTT            :: Bool
                       }

type MWParser m = ParserT Sources MWState m

instance HasReaderOptions MWState where
  extractReaderOptions :: MWState -> ReaderOptions
extractReaderOptions = MWState -> ReaderOptions
mwOptions

instance HasIdentifierList MWState where
  extractIdentifierList :: MWState -> Set Text
extractIdentifierList     = MWState -> Set Text
mwIdentifierList
  updateIdentifierList :: (Set Text -> Set Text) -> MWState -> MWState
updateIdentifierList Set Text -> Set Text
f MWState
st = MWState
st{ mwIdentifierList :: Set Text
mwIdentifierList = Set Text -> Set Text
f (Set Text -> Set Text) -> Set Text -> Set Text
forall a b. (a -> b) -> a -> b
$ MWState -> Set Text
mwIdentifierList MWState
st }

instance HasLogMessages MWState where
  addLogMessage :: LogMessage -> MWState -> MWState
addLogMessage LogMessage
m MWState
s = MWState
s{ mwLogMessages :: [LogMessage]
mwLogMessages = LogMessage
m LogMessage -> [LogMessage] -> [LogMessage]
forall a. a -> [a] -> [a]
: MWState -> [LogMessage]
mwLogMessages MWState
s }
  getLogMessages :: MWState -> [LogMessage]
getLogMessages = [LogMessage] -> [LogMessage]
forall a. [a] -> [a]
reverse ([LogMessage] -> [LogMessage])
-> (MWState -> [LogMessage]) -> MWState -> [LogMessage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MWState -> [LogMessage]
mwLogMessages

--
-- auxiliary functions
--

-- This is used to prevent exponential blowups for things like:
-- ''a'''a''a'''a''a'''a''a'''a
nested :: PandocMonad m => MWParser m a -> MWParser m a
nested :: forall (m :: * -> *) a.
PandocMonad m =>
MWParser m a -> MWParser m a
nested MWParser m a
p = do
  Int
nestlevel <- MWState -> Int
mwMaxNestingLevel (MWState -> Int)
-> ParsecT Sources MWState m MWState
-> ParsecT Sources MWState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecT Sources MWState m MWState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> ParsecT Sources MWState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources MWState m ())
-> Bool -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ Int
nestlevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  (MWState -> MWState) -> ParsecT Sources MWState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((MWState -> MWState) -> ParsecT Sources MWState m ())
-> (MWState -> MWState) -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ \MWState
st -> MWState
st{ mwMaxNestingLevel :: Int
mwMaxNestingLevel = MWState -> Int
mwMaxNestingLevel MWState
st Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 }
  a
res <- MWParser m a
p
  (MWState -> MWState) -> ParsecT Sources MWState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((MWState -> MWState) -> ParsecT Sources MWState m ())
-> (MWState -> MWState) -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ \MWState
st -> MWState
st{ mwMaxNestingLevel :: Int
mwMaxNestingLevel = Int
nestlevel }
  a -> MWParser m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
res

specialChars :: [Char]
specialChars :: [Char]
specialChars = [Char]
"'[]<=&*{}|\":\\"

spaceChars :: [Char]
spaceChars :: [Char]
spaceChars = [Char]
" \n\t"

sym :: PandocMonad m => Text -> MWParser m ()
sym :: forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
s = () ()
-> ParsecT Sources MWState m [Char] -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string ([Char] -> ParsecT Sources MWState m [Char])
-> [Char] -> ParsecT Sources MWState m [Char]
forall a b. (a -> b) -> a -> b
$ Text -> [Char]
T.unpack Text
s)

newBlockTags :: [Text]
newBlockTags :: [Text]
newBlockTags = [Text
"haskell",Text
"syntaxhighlight",Text
"source",Text
"gallery",Text
"references"]

isBlockTag' :: Tag Text -> Bool
isBlockTag' :: Tag Text -> Bool
isBlockTag' tag :: Tag Text
tag@(TagOpen Text
t [Attribute Text]
_) = (Tag Text -> Bool
isBlockTag Tag Text
tag Bool -> Bool -> Bool
|| Text
t Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
newBlockTags) Bool -> Bool -> Bool
&&
  Text
t Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Text]
eitherBlockOrInline
isBlockTag' (TagClose Text
"ref") = Bool
True -- needed so 'special' doesn't parse it
isBlockTag' tag :: Tag Text
tag@(TagClose Text
t) = (Tag Text -> Bool
isBlockTag Tag Text
tag Bool -> Bool -> Bool
|| Text
t Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
newBlockTags) Bool -> Bool -> Bool
&&
  Text
t Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Text]
eitherBlockOrInline
isBlockTag' Tag Text
tag = Tag Text -> Bool
isBlockTag Tag Text
tag

isInlineTag' :: Tag Text -> Bool
isInlineTag' :: Tag Text -> Bool
isInlineTag' (TagComment Text
_) = Bool
True
isInlineTag' (TagClose Text
"ref") = Bool
False -- see below inlineTag
isInlineTag' Tag Text
t              = Bool -> Bool
not (Tag Text -> Bool
isBlockTag' Tag Text
t)

eitherBlockOrInline :: [Text]
eitherBlockOrInline :: [Text]
eitherBlockOrInline = [Text
"applet", Text
"button", Text
"del", Text
"iframe", Text
"ins",
                               Text
"map", Text
"area", Text
"object"]

htmlComment :: PandocMonad m => MWParser m ()
htmlComment :: forall (m :: * -> *). PandocMonad m => MWParser m ()
htmlComment = () ()
-> ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isCommentTag

inlinesInTags :: PandocMonad m => Text -> MWParser m Inlines
inlinesInTags :: forall (m :: * -> *).
PandocMonad m =>
Text -> MWParser m (Many Inline)
inlinesInTags Text
tag = ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m (Many Inline)
 -> ParsecT Sources MWState m (Many Inline))
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ do
  (Tag Text
_,Text
raw) <- (Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen Text
tag [])
  if (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/') Text
raw   -- self-closing tag
     then Many Inline -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return Many Inline
forall a. Monoid a => a
mempty
     else Many Inline -> Many Inline
trimInlines (Many Inline -> Many Inline)
-> ([Many Inline] -> Many Inline) -> [Many Inline] -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
            ParsecT Sources MWState m (Many Inline)
-> ParserT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m [Many Inline]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline ((Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
tag))

blocksInTags :: PandocMonad m => Text -> MWParser m Blocks
blocksInTags :: forall (m :: * -> *). PandocMonad m => Text -> MWParser m Blocks
blocksInTags Text
tag = ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Blocks
 -> ParsecT Sources MWState m Blocks)
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ do
  (Tag Text
_,Text
raw) <- (Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen Text
tag [])
  let closer :: ParserT Sources MWState m (Tag Text, Text)
closer = if Text
tag Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"li"
                  then (Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
"li" :: Text))
                     ParserT Sources MWState m (Tag Text, Text)
-> ParserT Sources MWState m (Tag Text, Text)
-> ParserT Sources MWState m (Tag Text, Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParserT Sources MWState m (Tag Text, Text)
-> ParserT Sources MWState 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) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen (Text
"li" :: Text) [])
                          ParserT Sources MWState m (Tag Text, Text)
-> ParserT Sources MWState m (Tag Text, Text)
-> ParserT Sources MWState m (Tag Text, Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
"ol" :: Text))
                          ParserT Sources MWState m (Tag Text, Text)
-> ParserT Sources MWState m (Tag Text, Text)
-> ParserT Sources MWState m (Tag Text, Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
"ul" :: Text)))
                  else (Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
tag)
  if (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/') Text
raw   -- self-closing tag
     then Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
     else [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Blocks
-> ParserT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m [Blocks]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
block ParserT Sources MWState m (Tag Text, Text)
closer

textInTags :: PandocMonad m => Text -> MWParser m Text
textInTags :: forall (m :: * -> *). PandocMonad m => Text -> MWParser m Text
textInTags Text
tag = ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall a b. (a -> b) -> a -> b
$ do
  (Tag Text
_,Text
raw) <- (Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen Text
tag [])
  if (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/') Text
raw   -- self-closing tag
     then Text -> ParsecT Sources MWState m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
     else [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Char
-> ParserT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m [Char]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar ((Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
tag))

--
-- main parser
--

parseMediaWiki :: PandocMonad m => MWParser m Pandoc
parseMediaWiki :: forall (m :: * -> *). PandocMonad m => MWParser m Pandoc
parseMediaWiki = do
  Blocks
bs <- [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
block
  ParsecT Sources MWState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
  ParsecT Sources MWState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
  [Many Inline]
categoryLinks <- [Many Inline] -> [Many Inline]
forall a. [a] -> [a]
reverse ([Many Inline] -> [Many Inline])
-> (MWState -> [Many Inline]) -> MWState -> [Many Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MWState -> [Many Inline]
mwCategoryLinks (MWState -> [Many Inline])
-> ParsecT Sources MWState m MWState
-> ParsecT Sources MWState m [Many Inline]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m MWState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  let categories :: Blocks
categories = if [Many Inline] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Many Inline]
categoryLinks
                      then Blocks
forall a. Monoid a => a
mempty
                      else Many Inline -> Blocks
B.para (Many Inline -> Blocks) -> Many Inline -> Blocks
forall a b. (a -> b) -> a -> b
$ [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline) -> [Many Inline] -> Many Inline
forall a b. (a -> b) -> a -> b
$ Many Inline -> [Many Inline] -> [Many Inline]
forall a. a -> [a] -> [a]
intersperse Many Inline
B.space [Many Inline]
categoryLinks
  ParsecT Sources MWState m ()
forall (m :: * -> *) st s.
(PandocMonad m, HasLogMessages st) =>
ParserT s st m ()
reportLogMessages
  Pandoc -> MWParser m Pandoc
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> MWParser m Pandoc) -> Pandoc -> MWParser m Pandoc
forall a b. (a -> b) -> a -> b
$ Blocks -> Pandoc
B.doc (Blocks -> Pandoc) -> Blocks -> Pandoc
forall a b. (a -> b) -> a -> b
$ Blocks
bs Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
categories

--
-- block parsers
--

block :: PandocMonad m => MWParser m Blocks
block :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
block = do
  Blocks
res <- Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT Sources MWState m () -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources MWState m Char -> ParsecT Sources MWState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
table
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
header
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
hrule
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
orderedList
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
bulletList
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
definitionList
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT Sources MWState m () -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
htmlComment)
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
preformatted
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
blockTag
     MWParser m Blocks -> MWParser m Blocks -> MWParser 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
"mediawiki" (Text -> Blocks)
-> ParsecT Sources MWState m Text -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
template)
     MWParser m Blocks -> MWParser m Blocks -> MWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
para
  Text -> ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => Text -> m ()
trace (Int -> Text -> Text
T.take Int
60 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Block] -> Text
forall a. Show a => a -> Text
tshow ([Block] -> Text) -> [Block] -> Text
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
res)
  Blocks -> MWParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res

para :: PandocMonad m => MWParser m Blocks
para :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
para = do
  Many Inline
contents <- Many Inline -> Many Inline
trimInlines (Many Inline -> Many Inline)
-> ([Many Inline] -> Many Inline) -> [Many Inline] -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m [Many Inline]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline
  if (Inline -> Bool) -> Many Inline -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all (Inline -> Inline -> Bool
forall a. Eq a => a -> a -> Bool
==Inline
Space) Many Inline
contents
     then Blocks -> MWParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
     else case Many Inline -> [Inline]
forall a. Many a -> [a]
B.toList Many Inline
contents of
         -- For the MediaWiki format all images are considered figures
         [Image Attr
attr [Inline]
figureCaption (Text
src, Text
title)] ->
             Blocks -> MWParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MWParser m Blocks) -> Blocks -> MWParser m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Many Inline -> Text -> Text -> Blocks
B.simpleFigureWith
                 Attr
attr ([Inline] -> Many Inline
forall a. [a] -> Many a
B.fromList [Inline]
figureCaption) Text
src Text
title
         [Inline]
_ -> Blocks -> MWParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MWParser m Blocks) -> Blocks -> MWParser m Blocks
forall a b. (a -> b) -> a -> b
$ Many Inline -> Blocks
B.para Many Inline
contents

table :: PandocMonad m => MWParser m Blocks
table :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
table = do
  MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
tableStart
  [Attribute Text]
styles <- [Attribute Text]
-> ParsecT Sources MWState m [Attribute Text]
-> ParsecT Sources MWState m [Attribute Text]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] (ParsecT Sources MWState m [Attribute Text]
 -> ParsecT Sources MWState m [Attribute Text])
-> ParsecT Sources MWState m [Attribute Text]
-> ParsecT Sources MWState m [Attribute Text]
forall a b. (a -> b) -> a -> b
$
               ParsecT Sources MWState m [Attribute Text]
forall (m :: * -> *). PandocMonad m => MWParser m [Attribute Text]
parseAttrs ParsecT Sources MWState m [Attribute Text]
-> MWParser m () -> ParsecT Sources MWState m [Attribute Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources MWState m Char -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar ParsecT Sources MWState m [Attribute Text]
-> MWParser m () -> ParsecT Sources MWState m [Attribute Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources MWState m Char -> MWParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Char -> ParsecT Sources MWState 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 MWState m Char -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar
  MWParser m () -> MWParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (MWParser m () -> MWParser m ()) -> MWParser m () -> MWParser m ()
forall a b. (a -> b) -> a -> b
$ MWParser m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
template MWParser m Text -> MWParser m () -> MWParser m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources MWState m Char -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar
  MWParser m Text -> MWParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MWParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Text
blanklines
  let tableWidth :: Double
tableWidth = case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"width" [Attribute Text]
styles of
                         Just Text
w  -> Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 (Maybe Double -> Double) -> Maybe Double -> Double
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Double
parseWidth Text
w
                         Maybe Text
Nothing -> Double
1.0
  Many Inline
caption <- Many Inline
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Many Inline
forall a. Monoid a => a
mempty ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
tableCaption
  MWParser m () -> MWParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
rowsep
  Bool
hasheader <- Bool
-> ParsecT Sources MWState m Bool -> ParsecT Sources MWState 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 MWState m Bool -> ParsecT Sources MWState m Bool)
-> ParsecT Sources MWState m Bool -> ParsecT Sources MWState m Bool
forall a b. (a -> b) -> a -> b
$ Bool
True Bool
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Bool
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (MWParser m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces MWParser m ()
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'!')
  ([(Alignment, Double)]
cellspecs',[Blocks]
hdr) <- [((Alignment, Double), Blocks)]
-> ([(Alignment, Double)], [Blocks])
forall a b. [(a, b)] -> ([a], [b])
unzip ([((Alignment, Double), Blocks)]
 -> ([(Alignment, Double)], [Blocks]))
-> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
-> ParsecT Sources MWState m ([(Alignment, Double)], [Blocks])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
forall (m :: * -> *).
PandocMonad m =>
MWParser m [((Alignment, Double), Blocks)]
tableRow
  let widths :: [Double]
widths = ((Alignment, Double) -> Double)
-> [(Alignment, Double)] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map ((Double
tableWidth Double -> Double -> Double
forall a. Num a => a -> a -> a
*) (Double -> Double)
-> ((Alignment, Double) -> Double) -> (Alignment, Double) -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Alignment, Double) -> Double
forall a b. (a, b) -> b
snd) [(Alignment, Double)]
cellspecs'
  let restwidth :: Double
restwidth = Double
tableWidth Double -> Double -> Double
forall a. Num a => a -> a -> a
- [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Double]
widths
  let zerocols :: Int
zerocols = [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Double] -> Int) -> [Double] -> Int
forall a b. (a -> b) -> a -> b
$ (Double -> Bool) -> [Double] -> [Double]
forall a. (a -> Bool) -> [a] -> [a]
filter (Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
==Double
0.0) [Double]
widths
  let defaultwidth :: ColWidth
defaultwidth = if Int
zerocols Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Int
zerocols Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
widths
                        then ColWidth
ColWidthDefault
                        else Double -> ColWidth
ColWidth (Double -> ColWidth) -> Double -> ColWidth
forall a b. (a -> b) -> a -> b
$ Double
restwidth Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
zerocols
  let widths' :: [ColWidth]
widths' = (Double -> ColWidth) -> [Double] -> [ColWidth]
forall a b. (a -> b) -> [a] -> [b]
map (\Double
w -> if Double
w Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 then Double -> ColWidth
ColWidth Double
w else ColWidth
defaultwidth) [Double]
widths
  let cellspecs :: [(Alignment, ColWidth)]
cellspecs = [Alignment] -> [ColWidth] -> [(Alignment, ColWidth)]
forall a b. [a] -> [b] -> [(a, b)]
zip (((Alignment, Double) -> Alignment)
-> [(Alignment, Double)] -> [Alignment]
forall a b. (a -> b) -> [a] -> [b]
map (Alignment, Double) -> Alignment
forall a b. (a, b) -> a
fst [(Alignment, Double)]
cellspecs') [ColWidth]
widths'
  [[Blocks]]
rows' <- ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [[Blocks]]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources MWState m [Blocks]
 -> ParsecT Sources MWState m [[Blocks]])
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [[Blocks]]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m [Blocks]
 -> ParsecT Sources MWState m [Blocks])
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [Blocks]
forall a b. (a -> b) -> a -> b
$ MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
rowsep MWParser m ()
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [Blocks]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ((((Alignment, Double), Blocks) -> Blocks)
-> [((Alignment, Double), Blocks)] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map ((Alignment, Double), Blocks) -> Blocks
forall a b. (a, b) -> b
snd ([((Alignment, Double), Blocks)] -> [Blocks])
-> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
-> ParsecT Sources MWState m [Blocks]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
forall (m :: * -> *).
PandocMonad m =>
MWParser m [((Alignment, Double), Blocks)]
tableRow)
  MWParser m Text -> MWParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional MWParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Text
blanklines
  MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
tableEnd
  let cols :: Int
cols = [Blocks] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Blocks]
hdr
  let ([Blocks]
headers,[[Blocks]]
rows) = if Bool
hasheader
                          then ([Blocks]
hdr, [[Blocks]]
rows')
                          else (Int -> Blocks -> [Blocks]
forall a. Int -> a -> [a]
replicate Int
cols Blocks
forall a. Monoid a => a
mempty, [Blocks]
hdr[Blocks] -> [[Blocks]] -> [[Blocks]]
forall a. a -> [a] -> [a]
:[[Blocks]]
rows')
  let toRow :: [Blocks] -> Row
toRow = Attr -> [Cell] -> Row
Row Attr
nullAttr ([Cell] -> Row) -> ([Blocks] -> [Cell]) -> [Blocks] -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Blocks -> Cell) -> [Blocks] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map Blocks -> Cell
B.simpleCell
      toHeaderRow :: [Blocks] -> [Row]
toHeaderRow [Blocks]
l = [[Blocks] -> Row
toRow [Blocks]
l | Bool -> Bool
not ([Blocks] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Blocks]
l)]
  Blocks -> MWParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> MWParser m Blocks) -> Blocks -> MWParser m 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
$ Many Inline -> Blocks
B.plain Many Inline
caption)
                   [(Alignment, ColWidth)]
cellspecs
                   (Attr -> [Row] -> TableHead
TableHead Attr
nullAttr ([Row] -> TableHead) -> [Row] -> TableHead
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Row]
toHeaderRow [Blocks]
headers)
                   [Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] ([Row] -> TableBody) -> [Row] -> TableBody
forall a b. (a -> b) -> a -> b
$ ([Blocks] -> Row) -> [[Blocks]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map [Blocks] -> Row
toRow [[Blocks]]
rows]
                   (Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr [])

parseAttrs :: PandocMonad m => MWParser m [(Text,Text)]
parseAttrs :: forall (m :: * -> *). PandocMonad m => MWParser m [Attribute Text]
parseAttrs = ParsecT Sources MWState m (Attribute Text)
-> ParsecT Sources MWState m [Attribute Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources MWState m (Attribute Text)
forall (m :: * -> *). PandocMonad m => MWParser m (Attribute Text)
parseAttr

parseAttr :: PandocMonad m => MWParser m (Text, Text)
parseAttr :: forall (m :: * -> *). PandocMonad m => MWParser m (Attribute Text)
parseAttr = ParsecT Sources MWState m (Attribute Text)
-> ParsecT Sources MWState m (Attribute Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m (Attribute Text)
 -> ParsecT Sources MWState m (Attribute Text))
-> ParsecT Sources MWState m (Attribute Text)
-> ParsecT Sources MWState m (Attribute Text)
forall a b. (a -> b) -> a -> b
$ do
  ParsecT Sources MWState m Char -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar
  Text
k <- ParsecT Sources MWState m Char -> ParserT Sources MWState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter
  Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'='
  Text
v <- (Char -> ParsecT Sources MWState 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 MWState m Char
-> ParserT Sources MWState m Text -> ParserT Sources MWState m Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m Char -> ParserT Sources MWState m Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParserT s st m Char -> ParserT s st m end -> ParserT s st m Text
many1TillChar ((Char -> Bool) -> ParsecT Sources MWState 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')) (Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'))
       ParserT Sources MWState m Text
-> ParserT Sources MWState m Text -> ParserT Sources MWState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m Char -> ParserT Sources MWState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ((Char -> Bool) -> ParsecT Sources MWState 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 MWState m Char)
-> (Char -> Bool) -> ParsecT Sources MWState m Char
forall a b. (a -> b) -> a -> b
$ \Char
c -> Bool -> Bool
not (Char -> Bool
isSpace Char
c) Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'|')
  Attribute Text -> ParsecT Sources MWState m (Attribute Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
k,Text
v)

tableStart :: PandocMonad m => MWParser m ()
tableStart :: forall (m :: * -> *). PandocMonad m => MWParser m ()
tableStart = ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m () -> ParsecT Sources MWState m ())
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"{|"

tableEnd :: PandocMonad m => MWParser m ()
tableEnd :: forall (m :: * -> *). PandocMonad m => MWParser m ()
tableEnd = ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m () -> ParsecT Sources MWState m ())
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"|}"

rowsep :: PandocMonad m => MWParser m ()
rowsep :: forall (m :: * -> *). PandocMonad m => MWParser m ()
rowsep = ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m () -> ParsecT Sources MWState m ())
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"|-" ParsecT Sources MWState m ()
-> ParsecT Sources MWState m [Char] -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
               ParsecT Sources MWState m Char -> ParsecT Sources MWState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources MWState 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 MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources MWState m [Attribute Text]
-> ParsecT Sources MWState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources MWState m [Attribute Text]
forall (m :: * -> *). PandocMonad m => MWParser m [Attribute Text]
parseAttrs ParsecT Sources MWState m ()
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources MWState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Text
blanklines

cellsep :: PandocMonad m => MWParser m ()
cellsep :: forall (m :: * -> *). PandocMonad m => MWParser m ()
cellsep = ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m () -> ParsecT Sources MWState m ())
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ do
  Int
col <- SourcePos -> Int
sourceColumn (SourcePos -> Int)
-> ParsecT Sources MWState m SourcePos
-> ParsecT Sources MWState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  ParsecT Sources MWState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces
  let pipeSep :: ParsecT Sources u m ()
pipeSep = do
        Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|'
        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
oneOf [Char]
"-}+")
        if Int
col Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
           then ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (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
'|')
           else ParsecT Sources u m Char -> ParsecT Sources u m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (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
'|')
  let exclSep :: ParsecT Sources u m ()
exclSep = do
        Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'!'
        if Int
col Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
           then ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (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
'!')
           else ParsecT Sources u m Char -> ParsecT Sources u m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (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 MWState m ()
forall {u}. ParsecT Sources u m ()
pipeSep ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m ()
forall {u}. ParsecT Sources u m ()
exclSep

tableCaption :: PandocMonad m => MWParser m Inlines
tableCaption :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
tableCaption = ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m (Many Inline)
 -> ParsecT Sources MWState m (Many Inline))
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ do
  MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne
  MWParser m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces
  Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"|+"
  ParsecT Sources MWState m Text -> MWParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall a b. (a -> b) -> a -> b
$ MWParser m [Attribute Text]
forall (m :: * -> *). PandocMonad m => MWParser m [Attribute Text]
parseAttrs MWParser m [Attribute Text] -> MWParser m () -> MWParser m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> MWParser m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces MWParser m ()
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Sources MWState 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 MWState m Char
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Text
blanklines)
  Many Inline -> Many Inline
trimInlines (Many Inline -> Many Inline)
-> ([Many Inline] -> Many Inline) -> [Many Inline] -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
    ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m [Many Inline]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MWParser m () -> MWParser m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
cellsep MWParser m () -> MWParser m () -> MWParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
rowsep) MWParser m ()
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline)

tableRow :: PandocMonad m => MWParser m [((Alignment, Double), Blocks)]
tableRow :: forall (m :: * -> *).
PandocMonad m =>
MWParser m [((Alignment, Double), Blocks)]
tableRow = ParsecT Sources MWState m [((Alignment, Double), Blocks)]
-> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m [((Alignment, Double), Blocks)]
 -> ParsecT Sources MWState m [((Alignment, Double), Blocks)])
-> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
-> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
htmlComment ParsecT Sources MWState m ()
-> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
-> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m ((Alignment, Double), Blocks)
-> ParsecT Sources MWState m [((Alignment, Double), Blocks)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources MWState m ((Alignment, Double), Blocks)
forall (m :: * -> *).
PandocMonad m =>
MWParser m ((Alignment, Double), Blocks)
tableCell

tableCell :: PandocMonad m => MWParser m ((Alignment, Double), Blocks)
tableCell :: forall (m :: * -> *).
PandocMonad m =>
MWParser m ((Alignment, Double), Blocks)
tableCell = ParsecT Sources MWState m ((Alignment, Double), Blocks)
-> ParsecT Sources MWState m ((Alignment, Double), Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m ((Alignment, Double), Blocks)
 -> ParsecT Sources MWState m ((Alignment, Double), Blocks))
-> ParsecT Sources MWState m ((Alignment, Double), Blocks)
-> ParsecT Sources MWState m ((Alignment, Double), Blocks)
forall a b. (a -> b) -> a -> b
$ do
  MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
cellsep
  ParsecT Sources MWState m Char -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar
  [Attribute Text]
attrs <- [Attribute Text]
-> ParsecT Sources MWState m [Attribute Text]
-> ParsecT Sources MWState m [Attribute Text]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] (ParsecT Sources MWState m [Attribute Text]
 -> ParsecT Sources MWState m [Attribute Text])
-> ParsecT Sources MWState m [Attribute Text]
-> ParsecT Sources MWState m [Attribute Text]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m [Attribute Text]
-> ParsecT Sources MWState m [Attribute Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m [Attribute Text]
 -> ParsecT Sources MWState m [Attribute Text])
-> ParsecT Sources MWState m [Attribute Text]
-> ParsecT Sources MWState m [Attribute Text]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m [Attribute Text]
forall (m :: * -> *). PandocMonad m => MWParser m [Attribute Text]
parseAttrs ParsecT Sources MWState m [Attribute Text]
-> MWParser m () -> ParsecT Sources MWState m [Attribute Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MWParser m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces ParsecT Sources MWState m [Attribute Text]
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Attribute Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Sources MWState 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 MWState m [Attribute Text]
-> MWParser m () -> ParsecT Sources MWState m [Attribute Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
                                 ParsecT Sources MWState m Char -> MWParser 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 MWState 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 MWState m Char -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar
  SourcePos
pos' <- ParsecT Sources MWState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  Text
ls <- [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text -> ParsecT Sources MWState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (MWParser m () -> MWParser m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
cellsep MWParser m () -> MWParser m () -> MWParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
rowsep MWParser m () -> MWParser m () -> MWParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
tableEnd) MWParser m ()
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
                            (((Blocks, Text) -> Text
forall a b. (a, b) -> b
snd ((Blocks, Text) -> Text)
-> ParsecT Sources MWState m (Blocks, Text)
-> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m (Blocks, Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
table) ParsecT Sources MWState m Text
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState 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 MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar))
  Blocks
bs <- ParsecT Sources MWState m Blocks
-> Text -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (do SourcePos -> MWParser m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
pos'
                            [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
block) Text
ls
  let align :: Alignment
align = case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"align" [Attribute Text]
attrs of
                    Just Text
"left"   -> Alignment
AlignLeft
                    Just Text
"right"  -> Alignment
AlignRight
                    Just Text
"center" -> Alignment
AlignCenter
                    Maybe Text
_             -> Alignment
AlignDefault
  let width :: Double
width = case Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"width" [Attribute Text]
attrs of
                    Just Text
xs -> Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
0.0 (Maybe Double -> Double) -> Maybe Double -> Double
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Double
parseWidth Text
xs
                    Maybe Text
Nothing -> Double
0.0
  ((Alignment, Double), Blocks)
-> ParsecT Sources MWState m ((Alignment, Double), Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Alignment
align, Double
width), Blocks
bs)

parseWidth :: Text -> Maybe Double
parseWidth :: Text -> Maybe Double
parseWidth Text
s =
  case Text -> Maybe (Text, Char)
T.unsnoc Text
s of
    Just (Text
ds, Char
'%') | (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
ds -> Text -> Maybe Double
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> Maybe Double) -> Text -> Maybe Double
forall a b. (a -> b) -> a -> b
$ Text
"0." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ds
    Maybe (Text, Char)
_ -> Maybe Double
forall a. Maybe a
Nothing

template :: PandocMonad m => MWParser m Text
template :: forall (m :: * -> *). PandocMonad m => MWParser m Text
template = ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall a b. (a -> b) -> a -> b
$ do
  [Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"{{"
  ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState 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 MWState m Char -> ParsecT Sources MWState 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 MWState m Char -> ParsecT Sources MWState m Char)
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter ParsecT Sources MWState m Char
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit ParsecT Sources MWState m Char
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':'
  let chunk :: ParsecT Sources MWState m Text
chunk = ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
template ParsecT Sources MWState m Text
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
variable ParsecT Sources MWState m Text
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ([Char] -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"{}") ParsecT Sources MWState m Text
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState 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 MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
  [Text]
contents <- ParsecT Sources MWState m Text
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m Text
chunk (ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m [Char]
 -> ParsecT Sources MWState m [Char])
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"}}")
  Text -> ParsecT Sources MWState m Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources MWState m Text)
-> Text -> ParsecT Sources MWState m Text
forall a b. (a -> b) -> a -> b
$ Text
"{{" 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
"}}"

blockTag :: PandocMonad m => MWParser m Blocks
blockTag :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
blockTag = do
  (Tag Text
tag, Text
_) <- ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState 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 (ParsecT Sources MWState m (Tag Text, Text)
 -> ParsecT Sources MWState m (Tag Text, Text))
-> ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m (Tag Text, Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isBlockTag'
  case Tag Text
tag of
      TagOpen Text
"blockquote" [Attribute Text]
_ -> Blocks -> Blocks
B.blockQuote (Blocks -> Blocks) -> MWParser m Blocks -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Blocks
blocksInTags Text
"blockquote"
      TagOpen Text
"pre" [Attribute Text]
_ -> Text -> Blocks
B.codeBlock (Text -> Blocks) -> (Text -> Text) -> Text -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trimCode (Text -> Blocks)
-> ParsecT Sources MWState m Text -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Text
textInTags Text
"pre"
      TagOpen Text
"syntaxhighlight" [Attribute Text]
attrs -> Text -> [Attribute Text] -> MWParser m Blocks
forall (m :: * -> *).
PandocMonad m =>
Text -> [Attribute Text] -> MWParser m Blocks
syntaxhighlight Text
"syntaxhighlight" [Attribute Text]
attrs
      TagOpen Text
"source" [Attribute Text]
attrs -> Text -> [Attribute Text] -> MWParser m Blocks
forall (m :: * -> *).
PandocMonad m =>
Text -> [Attribute Text] -> MWParser m Blocks
syntaxhighlight Text
"source" [Attribute Text]
attrs
      TagOpen Text
"haskell" [Attribute Text]
_ -> Attr -> Text -> Blocks
B.codeBlockWith (Text
"",[Text
"haskell"],[]) (Text -> Blocks) -> (Text -> Text) -> Text -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trimCode (Text -> Blocks)
-> ParsecT Sources MWState m Text -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                                Text -> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Text
textInTags Text
"haskell"
      TagOpen Text
"gallery" [Attribute Text]
_ -> Text -> MWParser m Blocks
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Blocks
blocksInTags Text
"gallery"
      TagOpen Text
"p" [Attribute Text]
_ -> Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT Sources MWState m (Tag Text, Text) -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Tag Text
tag)
      TagClose Text
"p"  -> Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT Sources MWState m (Tag Text, Text) -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Tag Text
tag)
      Tag Text
_ -> Text -> Text -> Blocks
B.rawBlock Text
"html" (Text -> Blocks)
-> ((Tag Text, Text) -> Text) -> (Tag Text, Text) -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tag Text, Text) -> Text
forall a b. (a, b) -> b
snd ((Tag Text, Text) -> Blocks)
-> ParsecT Sources MWState m (Tag Text, Text) -> MWParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Tag Text
tag)

trimCode :: Text -> Text
trimCode :: Text -> Text
trimCode Text
t = case Text -> Maybe (Char, Text)
T.uncons Text
t of
  Just (Char
'\n', Text
xs) -> Text -> Text
stripTrailingNewlines Text
xs
  Maybe (Char, Text)
_               -> Text -> Text
stripTrailingNewlines Text
t

syntaxhighlight :: PandocMonad m => Text -> [Attribute Text] -> MWParser m Blocks
syntaxhighlight :: forall (m :: * -> *).
PandocMonad m =>
Text -> [Attribute Text] -> MWParser m Blocks
syntaxhighlight Text
tag [Attribute Text]
attrs = ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Blocks
 -> ParsecT Sources MWState m Blocks)
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ do
  let mblang :: Maybe Text
mblang = Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"lang" [Attribute Text]
attrs
  let mbstart :: Maybe Text
mbstart = Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"start" [Attribute Text]
attrs
  let mbline :: Maybe Text
mbline = Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"line" [Attribute Text]
attrs
  let classes :: [Text]
classes = Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList Maybe Text
mblang [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text] -> (Text -> [Text]) -> Maybe Text -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ([Text] -> Text -> [Text]
forall a b. a -> b -> a
const [Text
"numberLines"]) Maybe Text
mbline
  let kvs :: [Attribute Text]
kvs = [Attribute Text]
-> (Text -> [Attribute Text]) -> Maybe Text -> [Attribute Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Text
x -> [(Text
"startFrom",Text
x)]) Maybe Text
mbstart
  Text
contents <- Text -> MWParser m Text
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Text
textInTags Text
tag
  Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources MWState m Blocks)
-> Blocks -> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Blocks
B.codeBlockWith (Text
"",[Text]
classes,[Attribute Text]
kvs) (Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text
trimCode Text
contents

hrule :: PandocMonad m => MWParser m Blocks
hrule :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
hrule = Blocks
B.horizontalRule Blocks
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"----" ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Char -> ParsecT Sources MWState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources MWState 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 MWState m [Char]
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline)

guardColumnOne :: PandocMonad m => MWParser m ()
guardColumnOne :: forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne = ParsecT Sources MWState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition ParsecT Sources MWState m SourcePos
-> (SourcePos -> ParsecT Sources MWState m ())
-> ParsecT Sources MWState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourcePos
pos -> Bool -> ParsecT Sources MWState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (SourcePos -> Int
sourceColumn SourcePos
pos Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1)

preformatted :: PandocMonad m => MWParser m Blocks
preformatted :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
preformatted = ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Blocks
 -> ParsecT Sources MWState m Blocks)
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ do
  MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne
  Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' '
  let endline' :: ParsecT Sources u m (Many Inline)
endline' = Many Inline
B.linebreak Many Inline
-> ParsecT Sources u m Char -> ParsecT Sources u m (Many Inline)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ 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
try (ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources u m Char
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* 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
' ')
  let whitespace' :: ParsecT Sources st m (Many Inline)
whitespace' = Text -> Many Inline
B.str (Text -> Many Inline)
-> ParsecT Sources st m Text -> ParsecT Sources st m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Sources st m Char -> ParsecT Sources st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char (Char
'\160' Char -> ParserT Sources st m Char -> ParserT Sources st m Char
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParserT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar)
  let spToNbsp :: Char -> Char
spToNbsp Char
' ' = Char
'\160'
      spToNbsp Char
x   = Char
x
  let nowiki' :: ParsecT Sources MWState m (Many Inline)
nowiki' = [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> (Text -> [Many Inline]) -> Text -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Inline -> [Many Inline] -> [Many Inline]
forall a. a -> [a] -> [a]
intersperse Many Inline
B.linebreak ([Many Inline] -> [Many Inline])
-> (Text -> [Many Inline]) -> Text -> [Many Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Many Inline) -> [Text] -> [Many Inline]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Many Inline
B.str ([Text] -> [Many Inline])
-> (Text -> [Text]) -> Text -> [Many Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Text -> [Text]
T.lines (Text -> [Text]) -> (Text -> Text) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> Text -> Text
T.map Char -> Char
spToNbsp (Text -> Many Inline)
-> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try
                  ((Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen (Text
"nowiki" :: Text) []) ParserT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
                   ParsecT Sources MWState m Char
-> ParserT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar ((Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
"nowiki" :: Text))))
  let inline' :: ParsecT Sources MWState m (Many Inline)
inline' = ParsecT Sources MWState m (Many Inline)
forall {st}. ParsecT Sources st m (Many Inline)
whitespace' ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m (Many Inline)
forall {st}. ParsecT Sources st m (Many Inline)
endline' ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m (Many Inline)
nowiki'
                  ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Char -> MWParser 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 MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline MWParser m ()
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline)
  Many Inline
contents <- [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m [Many Inline]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources MWState m (Many Inline)
inline'
  let spacesStr :: Inline -> Bool
spacesStr (Str Text
xs) = (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isSpace Text
xs
      spacesStr Inline
_        = Bool
False
  if (Inline -> Bool) -> Many Inline -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all Inline -> Bool
spacesStr Many Inline
contents
     then Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
     else Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources MWState m Blocks)
-> Blocks -> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ Many Inline -> Blocks
B.para (Many Inline -> Blocks) -> Many Inline -> Blocks
forall a b. (a -> b) -> a -> b
$ Many Inline -> Many Inline
encode Many Inline
contents

encode :: Inlines -> Inlines
encode :: Many Inline -> Many Inline
encode = [Inline] -> Many Inline
forall a. [a] -> Many a
B.fromList ([Inline] -> Many Inline)
-> (Many Inline -> [Inline]) -> Many Inline -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> [Inline]
normalizeCode ([Inline] -> [Inline])
-> (Many Inline -> [Inline]) -> Many Inline -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Inline -> [Inline]
forall a. Many a -> [a]
B.toList (Many Inline -> [Inline])
-> (Many Inline -> Many Inline) -> Many Inline -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Inline) -> Many Inline -> Many Inline
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
strToCode
  where strToCode :: Inline -> Inline
strToCode (Str Text
s) = Attr -> Text -> Inline
Code (Text
"",[],[]) Text
s
        strToCode Inline
Space   = Attr -> Text -> Inline
Code (Text
"",[],[]) Text
" "
        strToCode  Inline
x      = Inline
x
        normalizeCode :: [Inline] -> [Inline]
normalizeCode []  = []
        normalizeCode (Code Attr
a1 Text
x : Code Attr
a2 Text
y : [Inline]
zs) | Attr
a1 Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
a2 =
          [Inline] -> [Inline]
normalizeCode ([Inline] -> [Inline]) -> [Inline] -> [Inline]
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Inline
Code Attr
a1 (Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
y) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
zs
        normalizeCode (Inline
x:[Inline]
xs) = Inline
x Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
normalizeCode [Inline]
xs

header :: PandocMonad m => MWParser m Blocks
header :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
header = ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Blocks
 -> ParsecT Sources MWState m Blocks)
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ do
  MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne
  Int
lev <- [Char] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Char] -> Int)
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Char -> ParsecT Sources MWState m [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'=')
  Bool -> MWParser m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MWParser m ()) -> Bool -> MWParser m ()
forall a b. (a -> b) -> a -> b
$ Int
lev Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
6
  Many Inline
contents <- Many Inline -> Many Inline
trimInlines (Many Inline -> Many Inline)
-> ([Many Inline] -> Many Inline) -> [Many Inline] -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Many Inline]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline (Int
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
lev (ParsecT Sources MWState m Char
 -> ParsecT Sources MWState m [Char])
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Char]
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'=')
  ReaderOptions
opts <- MWState -> ReaderOptions
mwOptions (MWState -> ReaderOptions)
-> ParsecT Sources MWState m MWState
-> ParsecT Sources MWState m ReaderOptions
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m MWState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Attr
attr <- (if Extension -> ReaderOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_gfm_auto_identifiers ReaderOptions
opts
              then Attr -> Attr
forall a. a -> a
id
              else Attr -> Attr
modifyIdentifier) (Attr -> Attr)
-> ParsecT Sources MWState m Attr -> ParsecT Sources MWState m Attr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Attr -> Many Inline -> ParsecT Sources MWState m Attr
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
 HasIdentifierList st) =>
Attr -> Many Inline -> ParserT s st m Attr
registerHeader Attr
nullAttr Many Inline
contents
  Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources MWState m Blocks)
-> Blocks -> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Many Inline -> Blocks
B.headerWith Attr
attr Int
lev Many Inline
contents

-- See #4731:
modifyIdentifier :: Attr -> Attr
modifyIdentifier :: Attr -> Attr
modifyIdentifier (Text
ident,[Text]
cl,[Attribute Text]
kv) = (Text
ident',[Text]
cl,[Attribute Text]
kv)
  where ident' :: Text
ident' = (Char -> Char) -> Text -> Text
T.map (\Char
c -> if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' then Char
'_' else Char
c) Text
ident

bulletList :: PandocMonad m => MWParser m Blocks
bulletList :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
bulletList = [Blocks] -> Blocks
B.bulletList ([Blocks] -> Blocks)
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
   (   ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem Char
'*')
   ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [Blocks]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ((Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen (Text
"ul" :: Text) []) ParserT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces ParsecT Sources MWState m ()
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [Blocks]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem Char
'*' ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
li) ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m ()
-> ParsecT Sources MWState m [Blocks]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
        ParserT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ((Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
"ul" :: Text)))) )

orderedList :: PandocMonad m => MWParser m Blocks
orderedList :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
orderedList =
       ([Blocks] -> Blocks
B.orderedList ([Blocks] -> Blocks)
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem Char
'#'))
   ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try
       (do (Tag Text
tag,Text
_) <- (Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen (Text
"ol" :: Text) [])
           ParsecT Sources MWState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
           [Blocks]
items <- ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem Char
'#' ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
li)
           ParserT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ((Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
"ol" :: Text)))
           let start :: Int
start = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> Maybe Int) -> Text -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"start" Tag Text
tag
           Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources MWState m Blocks)
-> Blocks -> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ ListAttributes -> [Blocks] -> Blocks
B.orderedListWith (Int
start, ListNumberStyle
DefaultStyle, ListNumberDelim
DefaultDelim) [Blocks]
items)

definitionList :: PandocMonad m => MWParser m Blocks
definitionList :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
definitionList = [(Many Inline, [Blocks])] -> Blocks
B.definitionList ([(Many Inline, [Blocks])] -> Blocks)
-> ParsecT Sources MWState m [(Many Inline, [Blocks])]
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline, [Blocks])
-> ParsecT Sources MWState m [(Many Inline, [Blocks])]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources MWState m (Many Inline, [Blocks])
forall (m :: * -> *).
PandocMonad m =>
MWParser m (Many Inline, [Blocks])
defListItem

defListItem :: PandocMonad m => MWParser m (Inlines, [Blocks])
defListItem :: forall (m :: * -> *).
PandocMonad m =>
MWParser m (Many Inline, [Blocks])
defListItem = ParsecT Sources MWState m (Many Inline, [Blocks])
-> ParsecT Sources MWState m (Many Inline, [Blocks])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m (Many Inline, [Blocks])
 -> ParsecT Sources MWState m (Many Inline, [Blocks]))
-> ParsecT Sources MWState m (Many Inline, [Blocks])
-> ParsecT Sources MWState m (Many Inline, [Blocks])
forall a b. (a -> b) -> a -> b
$ do
  Many Inline
terms <- [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ([Many Inline] -> [Many Inline]) -> [Many Inline] -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Inline -> [Many Inline] -> [Many Inline]
forall a. a -> [a] -> [a]
intersperse Many Inline
B.linebreak ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m [Many Inline]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
defListTerm
  -- we allow dd with no dt, or dt with no dd
  [Blocks]
defs  <- if Many Inline -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Many Inline
terms
              then ParsecT Sources MWState m [Char] -> ParsecT Sources MWState 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 MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m [Char]
 -> ParsecT Sources MWState m [Char])
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources MWState m Char -> ParsecT Sources MWState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 (Char -> ParsecT Sources MWState 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 MWState m ()
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"<math>") ParsecT Sources MWState m ()
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m [Blocks]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
                       ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem Char
':')
              else ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem Char
':')
  (Many Inline, [Blocks])
-> ParsecT Sources MWState m (Many Inline, [Blocks])
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Inline
terms, [Blocks]
defs)

defListTerm  :: PandocMonad m => MWParser m Inlines
defListTerm :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
defListTerm = do
  MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne
  Char -> ParsecT Sources MWState 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 MWState m Char -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar
  SourcePos
pos' <- ParsecT Sources MWState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  ParserT Sources MWState m Text
forall (m :: * -> *) st. Monad m => ParserT Sources st m Text
anyLine ParserT Sources MWState m Text
-> (Text -> MWParser m (Many Inline)) -> MWParser m (Many Inline)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= MWParser m (Many Inline) -> Text -> MWParser m (Many Inline)
forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (do SourcePos -> MWParser m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
pos'
                                  Many Inline -> Many Inline
trimInlines (Many Inline -> Many Inline)
-> ([Many Inline] -> Many Inline) -> [Many Inline] -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MWParser m (Many Inline) -> ParsecT Sources MWState m [Many Inline]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline)

listStart :: PandocMonad m => Char -> MWParser m ()
listStart :: forall (m :: * -> *). PandocMonad m => Char -> MWParser m ()
listStart Char
c = Char -> ParsecT Sources MWState 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 MWState m Char
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *). PandocMonad m => MWParser m Char
listStartChar

listStartChar :: PandocMonad m => MWParser m Char
listStartChar :: forall (m :: * -> *). PandocMonad m => MWParser m Char
listStartChar = [Char] -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
"*#;:"

anyListStart :: PandocMonad m => MWParser m Char
anyListStart :: forall (m :: * -> *). PandocMonad m => MWParser m Char
anyListStart = MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne MWParser m ()
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Char] -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
"*#:;"

li :: PandocMonad m => MWParser m Blocks
li :: forall (m :: * -> *). PandocMonad m => MWParser m Blocks
li = ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState 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 MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen (Text
"li" :: Text) [])) ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
     (Blocks -> Blocks
firstParaToPlain (Blocks -> Blocks)
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Blocks
blocksInTags Text
"li") ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources MWState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces

listItem :: PandocMonad m => Char -> MWParser m Blocks
listItem :: forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem Char
c = ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Blocks
 -> ParsecT Sources MWState m Blocks)
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ do
  MWParser m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
guardColumnOne
  [Char]
extras <- ParsecT Sources MWState m Char -> ParsecT Sources MWState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char)
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources MWState 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 MWState m Char
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *). PandocMonad m => MWParser m Char
listStartChar)
  if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
extras
     then Char -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem' Char
c
     else do
       ParsecT Sources MWState m Char -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar
       SourcePos
pos' <- ParsecT Sources MWState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
       Text
first <- [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
listChunk ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
       [Text]
rest <- ParsecT Sources MWState m Text -> ParsecT Sources MWState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many
                (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall a b. (a -> b) -> a -> b
$ [Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
extras ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *). PandocMonad m => MWParser m Char
listStartChar ParsecT Sources MWState m Char
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
                       ([Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
listChunk ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline))
       [Blocks]
contents <- ParserT Sources MWState m [Blocks]
-> Text -> ParserT Sources MWState m [Blocks]
forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (do SourcePos -> MWParser m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
pos'
                                       ParsecT Sources MWState m Blocks
-> ParserT Sources MWState m [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources MWState m Blocks
 -> ParserT Sources MWState m [Blocks])
-> ParsecT Sources MWState m Blocks
-> ParserT Sources MWState m [Blocks]
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem' Char
c)
                          ([Text] -> Text
T.unlines (Text
first Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
rest))
       case Char
c of
           Char
'*' -> Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources MWState m Blocks)
-> Blocks -> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
B.bulletList [Blocks]
contents
           Char
'#' -> Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources MWState m Blocks)
-> Blocks -> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
B.orderedList [Blocks]
contents
           Char
':' -> Blocks -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources MWState m Blocks)
-> Blocks -> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ [(Many Inline, [Blocks])] -> Blocks
B.definitionList [(Many Inline
forall a. Monoid a => a
mempty, [Blocks]
contents)]
           Char
_   -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- The point of this is to handle stuff like
-- * {{cite book
-- | blah
-- | blah
-- }}
-- * next list item
-- which seems to be valid mediawiki.
listChunk :: PandocMonad m => MWParser m Text
listChunk :: forall (m :: * -> *). PandocMonad m => MWParser m Text
listChunk = MWParser m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
template MWParser m Text -> MWParser m Text -> MWParser 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 MWState m Char -> MWParser 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 MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar

listItem' :: PandocMonad m => Char -> MWParser m Blocks
listItem' :: forall (m :: * -> *). PandocMonad m => Char -> MWParser m Blocks
listItem' Char
c = ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Blocks
 -> ParsecT Sources MWState m Blocks)
-> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ do
  Char -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Char -> MWParser m ()
listStart Char
c
  ParsecT Sources MWState m Char -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar
  SourcePos
pos' <- ParsecT Sources MWState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  Text
first <- [Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
listChunk ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  [Text]
rest <- ParsecT Sources MWState m Text -> ParsecT Sources MWState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources MWState 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 MWState m Char
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *). PandocMonad m => MWParser m Char
listStartChar ParsecT Sources MWState m Char
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
                   ([Text] -> Text
T.concat ([Text] -> Text)
-> ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
listChunk ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline))
  ParsecT Sources MWState m Blocks
-> Text -> ParsecT Sources MWState m Blocks
forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (do SourcePos -> MWParser m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
pos'
                      Blocks -> Blocks
firstParaToPlain (Blocks -> Blocks) -> ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT Sources MWState m [Blocks]
-> ParsecT Sources MWState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Blocks
-> ParsecT Sources MWState m [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
block)
      (Text -> ParsecT Sources MWState m Blocks)
-> Text -> ParsecT Sources MWState m Blocks
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text
first Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
rest

firstParaToPlain :: Blocks -> Blocks
firstParaToPlain :: Blocks -> Blocks
firstParaToPlain Blocks
contents =
  case Seq Block -> ViewL Block
forall a. Seq a -> ViewL a
viewl (Blocks -> Seq Block
forall a. Many a -> Seq a
B.unMany Blocks
contents) of
       Para [Inline]
xs :< Seq Block
ys -> Seq Block -> Blocks
forall a. Seq a -> Many a
B.Many (Seq Block -> Blocks) -> Seq Block -> Blocks
forall a b. (a -> b) -> a -> b
$ [Inline] -> Block
Plain [Inline]
xs Block -> Seq Block -> Seq Block
forall a. a -> Seq a -> Seq a
<| Seq Block
ys
       ViewL Block
_             -> Blocks
contents

--
-- inline parsers
--

inline :: PandocMonad m => MWParser m Inlines
inline :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline =  MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
whitespace
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
url
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
str
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
doubleQuotes
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
strong
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
emph
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
image
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
internalLink
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
externalLink
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
math
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inlineTag
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Inline -> Many Inline
forall a. a -> Many a
B.singleton (Inline -> Many Inline)
-> ParsecT Sources MWState m Inline -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Inline
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Inline
charRef
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inlineHtml
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> Text -> Many Inline
B.rawInline Text
"mediawiki" (Text -> Many Inline)
-> ParsecT Sources MWState m Text -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
variable)
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> Text -> Many Inline
B.rawInline Text
"mediawiki" (Text -> Many Inline)
-> ParsecT Sources MWState m Text -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
template)
      MWParser m (Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> MWParser m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
special

str :: PandocMonad m => MWParser m Inlines
str :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
str = Text -> Many Inline
B.str (Text -> Many Inline)
-> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Sources MWState m Char -> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ([Char] -> ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf ([Char] -> ParserT Sources MWState m Char)
-> [Char] -> ParserT Sources MWState m Char
forall a b. (a -> b) -> a -> b
$ [Char]
specialChars [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
spaceChars)

math :: PandocMonad m => MWParser m Inlines
math :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
math = (Text -> Many Inline
B.displayMath (Text -> Many Inline) -> (Text -> Text) -> Text -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trim (Text -> Many Inline)
-> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Char -> ParsecT Sources MWState m [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources MWState 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 MWState m [Char]
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Text
textInTags Text
"math"))
   ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> Many Inline
B.math (Text -> Many Inline) -> (Text -> Text) -> Text -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trim (Text -> Many Inline)
-> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Text
textInTags Text
"math")
   ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> Many Inline
B.displayMath (Text -> Many Inline) -> (Text -> Text) -> Text -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trim (Text -> Many Inline)
-> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m [Char]
forall {u}. ParsecT Sources u m [Char]
dmStart ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar ParsecT Sources MWState m [Char]
forall {u}. ParsecT Sources u m [Char]
dmEnd))
   ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> Many Inline
B.math (Text -> Many Inline) -> (Text -> Text) -> Text -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trim (Text -> Many Inline)
-> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m [Char]
forall {u}. ParsecT Sources u m [Char]
mStart ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar ((Char -> Bool) -> ParsecT Sources MWState 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 MWState m [Char]
forall {u}. ParsecT Sources u m [Char]
mEnd))
 where dmStart :: ParsecT Sources u m [Char]
dmStart = [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]
string [Char]
"\\["
       dmEnd :: ParsecT Sources u m [Char]
dmEnd   = 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
try ([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]
string [Char]
"\\]")
       mStart :: ParsecT Sources u m [Char]
mStart  = [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]
string [Char]
"\\("
       mEnd :: ParsecT Sources u m [Char]
mEnd    = 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
try ([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]
string [Char]
"\\)")

variable :: PandocMonad m => MWParser m Text
variable :: forall (m :: * -> *). PandocMonad m => MWParser m Text
variable = ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall a b. (a -> b) -> a -> b
$ do
  [Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"{{{"
  Text
contents <- ParserT Sources MWState m Char
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m [Char]
 -> ParsecT Sources MWState m [Char])
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"}}}")
  Text -> ParsecT Sources MWState m Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources MWState m Text)
-> Text -> ParsecT Sources MWState 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
"}}}"

singleParaToPlain :: Blocks -> Blocks
singleParaToPlain :: Blocks -> Blocks
singleParaToPlain Blocks
bs =
  case Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
bs of
    [Para [Inline]
ils] -> [Block] -> Blocks
forall a. [a] -> Many a
B.fromList [[Inline] -> Block
Plain [Inline]
ils]
    [Block]
_ -> Blocks
bs

inlineTag :: PandocMonad m => MWParser m Inlines
inlineTag :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inlineTag = do
  (Tag Text
tag, Text
_) <- ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState 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 (ParsecT Sources MWState m (Tag Text, Text)
 -> ParsecT Sources MWState m (Tag Text, Text))
-> ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m (Tag Text, Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isInlineTag'
  case Tag Text
tag of
       TagOpen Text
"ref" [Attribute Text]
_ -> Blocks -> Many Inline
B.note (Blocks -> Many Inline)
-> (Blocks -> Blocks) -> Blocks -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Blocks
singleParaToPlain (Blocks -> Many Inline)
-> ParsecT Sources MWState m Blocks -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Blocks
blocksInTags Text
"ref"
       TagOpen Text
"nowiki" [Attribute Text]
_ -> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MWParser m (Many Inline) -> MWParser m (Many Inline))
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall a b. (a -> b) -> a -> b
$ do
          (Tag Text
_,Text
raw) <- (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Tag Text
tag)
          if (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/') Text
raw
             then Many Inline -> MWParser m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return Many Inline
forall a. Monoid a => a
mempty
             else Text -> Many Inline
B.text (Text -> Many Inline) -> (Text -> Text) -> Text -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities (Text -> Many Inline)
-> ParsecT Sources MWState m Text -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                       ParserT Sources MWState m Char
-> ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text
manyTillChar ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar ((Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT 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
"nowiki" :: Text)))
       TagOpen Text
"br" [Attribute Text]
_ -> Many Inline
B.linebreak Many Inline
-> ParsecT Sources MWState m () -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ((Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen (Text
"br" :: Text) []) -- will get /> too
                            ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParserT Sources MWState m Char -> ParsecT Sources MWState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParserT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline)
       TagOpen Text
"strike" [Attribute Text]
_ -> Many Inline -> Many Inline
B.strikeout (Many Inline -> Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> MWParser m (Many Inline)
forall (m :: * -> *).
PandocMonad m =>
Text -> MWParser m (Many Inline)
inlinesInTags Text
"strike"
       TagOpen Text
"del" [Attribute Text]
_ -> Many Inline -> Many Inline
B.strikeout (Many Inline -> Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> MWParser m (Many Inline)
forall (m :: * -> *).
PandocMonad m =>
Text -> MWParser m (Many Inline)
inlinesInTags Text
"del"
       TagOpen Text
"sub" [Attribute Text]
_ -> Many Inline -> Many Inline
B.subscript (Many Inline -> Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> MWParser m (Many Inline)
forall (m :: * -> *).
PandocMonad m =>
Text -> MWParser m (Many Inline)
inlinesInTags Text
"sub"
       TagOpen Text
"sup" [Attribute Text]
_ -> Many Inline -> Many Inline
B.superscript (Many Inline -> Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> MWParser m (Many Inline)
forall (m :: * -> *).
PandocMonad m =>
Text -> MWParser m (Many Inline)
inlinesInTags Text
"sup"
       TagOpen Text
"code" [Attribute Text]
_ -> Many Inline -> Many Inline
encode (Many Inline -> Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> MWParser m (Many Inline)
forall (m :: * -> *).
PandocMonad m =>
Text -> MWParser m (Many Inline)
inlinesInTags Text
"code"
       TagOpen Text
"tt" [Attribute Text]
_ -> do
         Bool
inTT <- MWState -> Bool
mwInTT (MWState -> Bool)
-> ParsecT Sources MWState m MWState
-> ParsecT Sources MWState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m MWState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
         (MWState -> MWState) -> ParsecT Sources MWState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((MWState -> MWState) -> ParsecT Sources MWState m ())
-> (MWState -> MWState) -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ \MWState
st -> MWState
st{ mwInTT :: Bool
mwInTT = Bool
True }
         Many Inline
result <- Many Inline -> Many Inline
encode (Many Inline -> Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> MWParser m (Many Inline)
forall (m :: * -> *).
PandocMonad m =>
Text -> MWParser m (Many Inline)
inlinesInTags Text
"tt"
         (MWState -> MWState) -> ParsecT Sources MWState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((MWState -> MWState) -> ParsecT Sources MWState m ())
-> (MWState -> MWState) -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ \MWState
st -> MWState
st{ mwInTT :: Bool
mwInTT = Bool
inTT }
         Many Inline -> MWParser m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return Many Inline
result
       TagOpen Text
"hask" [Attribute Text]
_ -> Attr -> Text -> Many Inline
B.codeWith (Text
"",[Text
"haskell"],[]) (Text -> Many Inline)
-> ParsecT Sources MWState m Text -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => Text -> MWParser m Text
textInTags Text
"hask"
       Tag Text
_ -> Text -> Text -> Many Inline
B.rawInline Text
"html" (Text -> Many Inline)
-> ((Tag Text, Text) -> Text) -> (Tag Text, Text) -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tag Text, Text) -> Text
forall a b. (a, b) -> b
snd ((Tag Text, Text) -> Many Inline)
-> ParsecT Sources MWState m (Tag Text, Text)
-> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Tag Text
tag)

special :: PandocMonad m => MWParser m Inlines
special :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
special = Text -> Many Inline
B.str (Text -> Many Inline)
-> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 (ParserT Sources MWState m (Tag Text, Text)
-> ParserT Sources MWState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParserT s st m b -> ParserT s st m ()
notFollowedBy' ((Tag Text -> Bool) -> ParserT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isBlockTag') ParserT Sources MWState m ()
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
                                  [Char] -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
specialChars)

inlineHtml :: PandocMonad m => MWParser m Inlines
inlineHtml :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inlineHtml = Text -> Text -> Many Inline
B.rawInline Text
"html" (Text -> Many Inline)
-> ((Tag Text, Text) -> Text) -> (Tag Text, Text) -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tag Text, Text) -> Text
forall a b. (a, b) -> b
snd ((Tag Text, Text) -> Many Inline)
-> ParsecT Sources MWState m (Tag Text, Text)
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Tag Text -> Bool) -> ParsecT Sources MWState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParserT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isInlineTag'

whitespace :: PandocMonad m => MWParser m Inlines
whitespace :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
whitespace = Many Inline
B.space Many Inline
-> ParsecT Sources MWState m ()
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT Sources MWState m Char -> ParsecT Sources MWState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar ParsecT Sources MWState m ()
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
htmlComment)
         ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Many Inline
B.softbreak Many Inline
-> ParsecT Sources MWState m ()
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
endline

endline :: PandocMonad m => MWParser m ()
endline :: forall (m :: * -> *). PandocMonad m => MWParser m ()
endline = () ()
-> ParsecT Sources MWState m Char -> ParsecT Sources MWState m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources MWState m Char -> ParsecT Sources MWState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources MWState m Char
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
                     ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar ParsecT Sources MWState m Char
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
                     ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources MWState m Char
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
                     ParserT Sources MWState m Blocks -> ParsecT Sources MWState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParserT s st m b -> ParserT s st m ()
notFollowedBy' ParserT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
hrule ParsecT Sources MWState m Char
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
                     ParsecT Sources MWState m () -> ParsecT Sources MWState 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 MWState m ()
forall (m :: * -> *). PandocMonad m => MWParser m ()
tableStart ParsecT Sources MWState m Char
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
                     ParserT Sources MWState m Blocks -> ParsecT Sources MWState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParserT s st m b -> ParserT s st m ()
notFollowedBy' ParserT Sources MWState m Blocks
forall (m :: * -> *). PandocMonad m => MWParser m Blocks
header ParsecT Sources MWState m Char
-> ParsecT Sources MWState m () -> ParsecT Sources MWState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*
                     ParsecT Sources MWState m Char -> ParsecT Sources MWState 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 MWState m Char
forall (m :: * -> *). PandocMonad m => MWParser m Char
anyListStart)

imageIdentifiers :: PandocMonad m => [MWParser m ()]
imageIdentifiers :: forall (m :: * -> *). PandocMonad m => [MWParser m ()]
imageIdentifiers = [Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym (Text
identifier Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":") | Text
identifier <- [Text]
identifiers]
    where identifiers :: [Text]
identifiers = [Text
"File", Text
"Image", Text
"Archivo", Text
"Datei", Text
"Fichier",
                         Text
"Bild"]

image :: PandocMonad m => MWParser m Inlines
image :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
image = ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m (Many Inline)
 -> ParsecT Sources MWState m (Many Inline))
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ do
  Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"[["
  [MWParser m ()] -> MWParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [MWParser m ()]
forall (m :: * -> *). PandocMonad m => [MWParser m ()]
imageIdentifiers
  Text
fname <- Text -> Text
addUnderscores (Text -> Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Sources MWState m Char -> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
many1Char ([Char] -> ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"|]")
  [Text]
_ <- ParsecT Sources MWState m Text -> ParsecT Sources MWState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
imageOption
  [Text]
dims <- ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' ParserT Sources MWState m Char
-> ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m [Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Text
-> ParserT Sources MWState m Char
-> ParsecT Sources MWState m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
sepBy (ParserT Sources MWState m Char -> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
manyChar ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit) (Char -> ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'x') ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m [Char]
-> ParsecT Sources MWState m [Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* [Char] -> ParsecT Sources MWState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"px")
          ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState m [Text]
-> ParsecT Sources MWState 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 MWState m [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return []
  [Text]
_ <- ParsecT Sources MWState m Text -> ParsecT Sources MWState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources MWState m Text
forall (m :: * -> *). PandocMonad m => MWParser m Text
imageOption
  let kvs :: [Attribute Text]
kvs = case [Text]
dims of
              [Text
w]    -> [(Text
"width", Text
w)]
              [Text
w, Text
h] -> [(Text
"width", Text
w), (Text
"height", Text
h)]
              [Text]
_      -> []
  let attr :: (Text, [a], [Attribute Text])
attr = (Text
"", [], [Attribute Text]
kvs)
  Many Inline
caption <-   (Text -> Many Inline
B.str Text
fname Many Inline
-> MWParser m () -> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"]]")
           ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' ParserT Sources MWState m Char
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ([Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline)
-> MWParser m () -> ParsecT Sources MWState m [Many Inline]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline (Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"]]")))
  Many Inline -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Inline -> ParsecT Sources MWState m (Many Inline))
-> Many Inline -> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Many Inline -> Many Inline
B.imageWith Attr
forall {a}. (Text, [a], [Attribute Text])
attr Text
fname (Many Inline -> Text
forall a. Walkable Inline a => a -> Text
stringify Many Inline
caption) Many Inline
caption

imageOption :: PandocMonad m => MWParser m Text
imageOption :: forall (m :: * -> *). PandocMonad m => MWParser m Text
imageOption = ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources MWState 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 MWState m Char
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m Text
forall {u}. ParsecT Sources u m Text
opt
  where
    opt :: ParsecT Sources u m Text
opt = ParsecT Sources u m Text -> ParsecT Sources u m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Text] -> ParsecT Sources u m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
[Text] -> ParserT s st m Text
oneOfStrings [ Text
"border", Text
"thumbnail", Text
"frameless"
                            , Text
"thumb", Text
"upright", Text
"left", Text
"right"
                            , Text
"center", Text
"none", Text
"baseline", Text
"sub"
                            , Text
"super", Text
"top", Text
"text-top", Text
"middle"
                            , Text
"bottom", Text
"text-bottom" ])
      ParsecT Sources u m Text
-> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text -> ParsecT Sources u m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
"frame")
      ParsecT Sources u m Text
-> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Text] -> ParsecT Sources u m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
[Text] -> ParserT s st m Text
oneOfStrings [Text
"link=",Text
"alt=",Text
"page=",Text
"class="] ParsecT Sources u m Text
-> ParsecT Sources u m [Char] -> ParsecT Sources u m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* 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]
many ([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
noneOf [Char]
"|]"))

addUnderscores :: Text -> Text
addUnderscores :: Text -> Text
addUnderscores = Text -> [Text] -> Text
T.intercalate Text
"_" ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
splitTextBy Char -> Bool
sep
  where
    sep :: Char -> Bool
sep Char
c = Char -> Bool
isSpace Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_'

internalLink :: PandocMonad m => MWParser m Inlines
internalLink :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
internalLink = ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m (Many Inline)
 -> ParsecT Sources MWState m (Many Inline))
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ do
  Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"[["
  Text
pagename <- [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)
-> ParsecT Sources MWState m Text -> ParsecT Sources MWState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Sources MWState m Char -> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
manyChar ([Char] -> ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"|]")
  Many Inline
label <- Many Inline
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Text -> Many Inline
B.text Text
pagename) (ParsecT Sources MWState m (Many Inline)
 -> ParsecT Sources MWState m (Many Inline))
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ Char -> ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' ParserT Sources MWState m Char
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
             (  ([Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m [Many Inline]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParserT Sources MWState m Char -> MWParser m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']') MWParser m ()
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline))
             -- the "pipe trick"
             -- [[Help:Contents|] -> "Contents"
             ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Many Inline -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Many Inline
B.text (Text -> Many Inline) -> Text -> Many Inline
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
1 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
':') Text
pagename) )
  Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"]]"
  Many Inline
linktrail <- Text -> Many Inline
B.text (Text -> Many Inline)
-> ParsecT Sources MWState m Text
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParserT Sources MWState m Char -> ParsecT Sources MWState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParserT s st m Char -> ParserT s st m Text
manyChar ParserT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter
  let link :: Many Inline
link = Text -> Text -> Many Inline -> Many Inline
B.link (Text -> Text
addUnderscores Text
pagename) Text
"wikilink" (Many Inline
label Many Inline -> Many Inline -> Many Inline
forall a. Semigroup a => a -> a -> a
<> Many Inline
linktrail)
  if Text
"Category:" Text -> Text -> Bool
`T.isPrefixOf` Text
pagename
     then do
       (MWState -> MWState) -> MWParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((MWState -> MWState) -> MWParser m ())
-> (MWState -> MWState) -> MWParser m ()
forall a b. (a -> b) -> a -> b
$ \MWState
st -> MWState
st{ mwCategoryLinks :: [Many Inline]
mwCategoryLinks = Many Inline
link Many Inline -> [Many Inline] -> [Many Inline]
forall a. a -> [a] -> [a]
: MWState -> [Many Inline]
mwCategoryLinks MWState
st }
       Many Inline -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return Many Inline
forall a. Monoid a => a
mempty
     else Many Inline -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return Many Inline
link

externalLink :: PandocMonad m => MWParser m Inlines
externalLink :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
externalLink = ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources MWState m (Many Inline)
 -> ParsecT Sources MWState m (Many Inline))
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ do
  Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'['
  (Text
_, Text
src) <- ParserT Sources MWState m (Attribute Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m (Attribute Text)
uri
  Many Inline
lab <- ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Many Inline -> Many Inline
trimInlines (Many Inline -> Many Inline)
-> ([Many Inline] -> Many Inline) -> [Many Inline] -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
              (ParsecT Sources MWState m Char -> ParsecT Sources MWState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources MWState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar ParsecT Sources MWState m ()
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m [Many Inline]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m Char
-> ParsecT Sources MWState m [Many Inline]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline (Char -> ParsecT Sources MWState 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 MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> do Char -> ParsecT Sources MWState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']'
              Int
num <- MWState -> Int
mwNextLinkNumber (MWState -> Int)
-> ParsecT Sources MWState m MWState
-> ParsecT Sources MWState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m MWState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
              (MWState -> MWState) -> ParsecT Sources MWState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((MWState -> MWState) -> ParsecT Sources MWState m ())
-> (MWState -> MWState) -> ParsecT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ \MWState
st -> MWState
st{ mwNextLinkNumber :: Int
mwNextLinkNumber = Int
num Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
              Many Inline -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Inline -> ParsecT Sources MWState m (Many Inline))
-> Many Inline -> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ Text -> Many Inline
B.str (Text -> Many Inline) -> Text -> Many Inline
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. Show a => a -> Text
tshow Int
num
  Many Inline -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Inline -> ParsecT Sources MWState m (Many Inline))
-> Many Inline -> ParsecT Sources MWState m (Many Inline)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Many Inline -> Many Inline
B.link Text
src Text
"" Many Inline
lab

url :: PandocMonad m => MWParser m Inlines
url :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
url = do
  (Text
orig, Text
src) <- ParserT Sources MWState m (Attribute Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m (Attribute Text)
uri
  Many Inline -> MWParser m (Many Inline)
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Inline -> MWParser m (Many Inline))
-> Many Inline -> MWParser m (Many Inline)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Many Inline -> Many Inline
B.link Text
src Text
"" (Text -> Many Inline
B.str Text
orig)

-- | Parses a list of inlines between start and end delimiters.
inlinesBetween :: (PandocMonad m, Show b) => MWParser m a -> MWParser m b -> MWParser m Inlines
inlinesBetween :: forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
MWParser m a -> MWParser m b -> MWParser m (Many Inline)
inlinesBetween MWParser m a
start MWParser m b
end =
  Many Inline -> Many Inline
trimInlines (Many Inline -> Many Inline)
-> ([Many Inline] -> Many Inline) -> [Many Inline] -> Many Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Many Inline] -> Many Inline
forall a. Monoid a => [a] -> a
mconcat ([Many Inline] -> Many Inline)
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m [Many Inline]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MWParser m a
start MWParser m a
-> ParsecT Sources MWState m [Many Inline]
-> ParsecT Sources MWState m [Many Inline]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources MWState m (Many Inline)
-> MWParser m b -> ParsecT Sources MWState m [Many Inline]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParserT s st m a -> ParserT s st m end -> ParserT s st m [a]
many1Till ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
inline MWParser m b
end)

emph :: PandocMonad m => MWParser m Inlines
emph :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
emph = Many Inline -> Many Inline
B.emph (Many Inline -> Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a.
PandocMonad m =>
MWParser m a -> MWParser m a
nested (MWParser m ()
-> MWParser m () -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
MWParser m a -> MWParser m b -> MWParser m (Many Inline)
inlinesBetween MWParser m ()
start MWParser m ()
end)
    where start :: MWParser m ()
start = Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"''"
          end :: MWParser m ()
end   = MWParser m () -> MWParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (MWParser m () -> MWParser m ()) -> MWParser m () -> MWParser m ()
forall a b. (a -> b) -> a -> b
$ MWParser m () -> MWParser m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParserT s st m b -> ParserT s st m ()
notFollowedBy' (() () -> ParsecT Sources MWState m (Many Inline) -> MWParser m ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
strong) MWParser m () -> MWParser m () -> MWParser m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"''"

strong :: PandocMonad m => MWParser m Inlines
strong :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
strong = Many Inline -> Many Inline
B.strong (Many Inline -> Many Inline)
-> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m (Many Inline)
-> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) a.
PandocMonad m =>
MWParser m a -> MWParser m a
nested (MWParser m ()
-> MWParser m () -> ParsecT Sources MWState m (Many Inline)
forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
MWParser m a -> MWParser m b -> MWParser m (Many Inline)
inlinesBetween MWParser m ()
start MWParser m ()
end)
    where start :: MWParser m ()
start = Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"'''"
          end :: MWParser m ()
end   = Text -> MWParser m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"'''"

doubleQuotes :: PandocMonad m => MWParser m Inlines
doubleQuotes :: forall (m :: * -> *). PandocMonad m => MWParser m (Many Inline)
doubleQuotes = do
  Extension -> ParserT Sources MWState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParserT s st m ()
guardEnabled Extension
Ext_smart
  Bool
inTT <- MWState -> Bool
mwInTT (MWState -> Bool)
-> ParsecT Sources MWState m MWState
-> ParsecT Sources MWState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources MWState m MWState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> ParserT Sources MWState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not Bool
inTT)
  Many Inline -> Many Inline
B.doubleQuoted (Many Inline -> Many Inline)
-> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MWParser m (Many Inline) -> MWParser m (Many Inline)
forall (m :: * -> *) a.
PandocMonad m =>
MWParser m a -> MWParser m a
nested (MWParser m Char
-> ParserT Sources MWState m () -> MWParser m (Many Inline)
forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
MWParser m a -> MWParser m b -> MWParser m (Many Inline)
inlinesBetween MWParser m Char
openDoubleQuote ParserT Sources MWState m ()
closeDoubleQuote)
    where openDoubleQuote :: MWParser m Char
openDoubleQuote = Text -> ParserT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"\"" ParserT Sources MWState m () -> MWParser m Char -> MWParser m Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MWParser m Char -> MWParser m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead MWParser m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
nonspaceChar
          closeDoubleQuote :: ParserT Sources MWState m ()
closeDoubleQuote = ParserT Sources MWState m () -> ParserT Sources MWState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParserT Sources MWState m () -> ParserT Sources MWState m ())
-> ParserT Sources MWState m () -> ParserT Sources MWState m ()
forall a b. (a -> b) -> a -> b
$ Text -> ParserT Sources MWState m ()
forall (m :: * -> *). PandocMonad m => Text -> MWParser m ()
sym Text
"\""