{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections     #-}
{-# LANGUAGE ViewPatterns      #-}
module Text.Pandoc.Readers.DokuWiki (readDokuWiki) where
import Control.Monad
import Control.Monad.Except (throwError)
import Data.Char (isAlphaNum, isDigit)
import qualified Data.Foldable as F
import Data.Maybe (fromMaybe, catMaybes)
import Data.Bifunctor (second)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (enclosed)
import Text.Pandoc.Shared (trim, stringify, tshow)
import Data.List (isPrefixOf, isSuffixOf)
import qualified Safe
readDokuWiki :: (PandocMonad m, ToSources a)
             => ReaderOptions
             -> a
             -> m Pandoc
readDokuWiki :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readDokuWiki ReaderOptions
opts a
s = do
  let sources :: Sources
sources = a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s
  Either ParseError Pandoc
res <- ParsecT Sources ParserState m Pandoc
-> ParserState
-> SourceName
-> Sources
-> m (Either ParseError Pandoc)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a)
runParserT ParsecT Sources ParserState m Pandoc
forall (m :: * -> *). PandocMonad m => DWParser m Pandoc
parseDokuWiki ParserState
forall a. Default a => a
def {stateOptions :: ReaderOptions
stateOptions = ReaderOptions
opts }
           (Sources -> SourceName
initialSourceName Sources
sources) Sources
sources
  case Either ParseError Pandoc
res of
       Left ParseError
e  -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Sources -> ParseError -> PandocError
fromParsecError Sources
sources ParseError
e
       Right Pandoc
d -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
d
type DWParser = ParsecT Sources ParserState
eol :: (Stream s m Char, UpdateSourcePos s Char) => ParsecT s st m ()
eol :: forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
eol = ParsecT s st m Char -> ParsecT s st m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT s st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT s st m () -> ParsecT s st m () -> ParsecT s st m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT s st m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
guardColumnOne :: PandocMonad m => DWParser m ()
guardColumnOne :: forall (m :: * -> *). PandocMonad m => DWParser m ()
guardColumnOne = ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition ParsecT Sources ParserState m SourcePos
-> (SourcePos -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \SourcePos
pos -> Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (SourcePos -> Column
sourceColumn SourcePos
pos Column -> Column -> Bool
forall a. Eq a => a -> a -> Bool
== Column
1)
parseDokuWiki :: PandocMonad m => DWParser m Pandoc
parseDokuWiki :: forall (m :: * -> *). PandocMonad m => DWParser m Pandoc
parseDokuWiki =
  Blocks -> Pandoc
B.doc (Blocks -> Pandoc) -> ([Blocks] -> Blocks) -> [Blocks] -> Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Pandoc)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Pandoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
block ParsecT Sources ParserState m Pandoc
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Pandoc
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces ParsecT Sources ParserState m Pandoc
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Pandoc
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
codeLanguage :: PandocMonad m => DWParser m (Text, [Text], [(Text, Text)])
codeLanguage :: forall (m :: * -> *).
PandocMonad m =>
DWParser m (Text, [Text], [(Text, Text)])
codeLanguage = ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
-> ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
 -> ParsecT Sources ParserState m (Text, [Text], [(Text, Text)]))
-> ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
-> ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
forall a b. (a -> b) -> a -> b
$ do
  Text
rawLang <- Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"-" (ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>')))
  let attr :: [Text]
attr = case Text
rawLang of
               Text
"-" -> []
               Text
l -> [Text
l]
  (Text, [Text], [(Text, Text)])
-> ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
"", [Text]
attr, [])
codeTag :: PandocMonad m
        => ((Text, [Text], [(Text, Text)]) -> Text -> a)
        -> Text
        -> DWParser m a
codeTag :: forall (m :: * -> *) a.
PandocMonad m =>
((Text, [Text], [(Text, Text)]) -> Text -> a)
-> Text -> DWParser m a
codeTag (Text, [Text], [(Text, Text)]) -> Text -> a
f Text
tag = ParsecT Sources ParserState m a -> ParsecT Sources ParserState m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m a
 -> ParsecT Sources ParserState m a)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m a
forall a b. (a -> b) -> a -> b
$ (Text, [Text], [(Text, Text)]) -> Text -> a
f
  ((Text, [Text], [(Text, Text)]) -> Text -> a)
-> ParsecT Sources ParserState m Char
-> ParsecT
     Sources ParserState m ((Text, [Text], [(Text, Text)]) -> Text -> a)
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$  Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<'
  ParsecT
  Sources ParserState m ((Text, [Text], [(Text, Text)]) -> Text -> a)
-> ParsecT Sources ParserState m Text
-> ParsecT
     Sources ParserState m ((Text, [Text], [(Text, Text)]) -> Text -> a)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*  Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
tag
  ParsecT
  Sources ParserState m ((Text, [Text], [(Text, Text)]) -> Text -> a)
-> ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
-> ParsecT Sources ParserState m (Text -> a)
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
forall (m :: * -> *).
PandocMonad m =>
DWParser m (Text, [Text], [(Text, Text)])
codeLanguage
  ParsecT Sources ParserState m (Text -> a)
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m (Text -> a)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
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 ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>')
  ParsecT Sources ParserState m (Text -> a)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Text -> a)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*  ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m SourceName
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 ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
eol)
  ParsecT Sources ParserState m (Text -> a)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m a
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m SourceName
 -> ParsecT Sources ParserState m SourceName)
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"</" ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m SourceName
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
tag ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>')
inline' :: PandocMonad m => DWParser m B.Inlines
inline' :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline' = DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
whitespace
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline''
inline'' :: PandocMonad m => DWParser m B.Inlines
inline'' :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline'' = DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
br
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
bold
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
italic
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
underlined
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
nowiki
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
percent
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
link
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
image
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
monospaced
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
subscript
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
superscript
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
deleted
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
footnote
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inlineCode
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inlineFile
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inlineRaw
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
math
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
autoLink
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
autoEmail
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
notoc
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
nocache
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
str
      DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
symbol
      DWParser m Inlines -> SourceName -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> SourceName -> ParsecT s u m a
<?> SourceName
"inline"
inlineUnconsolidatedWhitespace :: PandocMonad m => DWParser m B.Inlines
inlineUnconsolidatedWhitespace :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inlineUnconsolidatedWhitespace = (Inlines
B.space Inlines
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Inlines
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar) ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline'
inline :: PandocMonad m => DWParser m B.Inlines
inline :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline = DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
endline DWParser m Inlines -> DWParser m Inlines -> DWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline'
endline :: PandocMonad m => DWParser m B.Inlines
endline :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
endline = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
B.softbreak Inlines
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
linebreak
whitespace :: PandocMonad m => DWParser m B.Inlines
whitespace :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
whitespace = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
B.space Inlines
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
br :: PandocMonad m => DWParser m B.Inlines
br :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
br = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
B.linebreak Inlines
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Inlines
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"\\\\" ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
space
linebreak :: PandocMonad m => DWParser m B.Inlines
linebreak :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
linebreak = ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ParsecT Sources ParserState m Inlines
forall {u}. ParsecT Sources u m Inlines
lastNewline ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
innerNewline)
  where lastNewline :: ParsecT Sources u m Inlines
lastNewline  = Inlines
forall a. Monoid a => a
mempty Inlines -> ParsecT Sources u m () -> ParsecT Sources u m Inlines
forall a b. a -> ParsecT Sources u m b -> ParsecT Sources u m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
        innerNewline :: ParsecT Sources ParserState m Inlines
innerNewline = Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
B.space
between :: (Monoid c, PandocMonad m, Show b)
        => DWParser m a -> DWParser m b -> (DWParser m b -> DWParser m c)
        -> DWParser m c
between :: forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
DWParser m a
-> DWParser m b -> (DWParser m b -> DWParser m c) -> DWParser m c
between DWParser m a
start DWParser m b
end DWParser m b -> DWParser m c
p =
  [c] -> c
forall a. Monoid a => [a] -> a
mconcat ([c] -> c) -> ParsecT Sources ParserState m [c] -> DWParser m c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m [c]
-> ParsecT Sources ParserState m [c]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (DWParser m a
start DWParser m a
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
whitespace ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [c]
-> ParsecT Sources ParserState m [c]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> DWParser m c -> DWParser m b -> ParsecT Sources ParserState m [c]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till (DWParser m b -> DWParser m c
p DWParser m b
end) DWParser m b
end)
enclosed :: (Monoid b, PandocMonad m, Show a)
         => DWParser m a -> (DWParser m a -> DWParser m b) -> DWParser m b
enclosed :: forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
DWParser m a -> (DWParser m a -> DWParser m b) -> DWParser m b
enclosed DWParser m a
sep DWParser m a -> DWParser m b
p = DWParser m a
-> DWParser m a -> (DWParser m a -> DWParser m b) -> DWParser m b
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
DWParser m a
-> DWParser m b -> (DWParser m b -> DWParser m c) -> DWParser m c
between DWParser m a
sep (DWParser m a -> DWParser m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try DWParser m a
sep) DWParser m a -> DWParser m b
p
nestedInlines :: (Show a, PandocMonad m)
              => DWParser m a -> DWParser m B.Inlines
nestedInlines :: forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines DWParser m a
end = ParsecT Sources ParserState m Inlines
innerSpace ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
nestedInline
  where
    innerSpace :: ParsecT Sources ParserState m Inlines
innerSpace   = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
whitespace ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* DWParser m a -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy DWParser m a
end
    nestedInline :: ParsecT Sources ParserState m Inlines
nestedInline = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
whitespace ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline
bold :: PandocMonad m => DWParser m B.Inlines
bold :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
bold = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.strong (Inlines -> Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
DWParser m a -> (DWParser m a -> DWParser m b) -> DWParser m b
enclosed (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"**") DWParser m SourceName -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines
italic :: PandocMonad m => DWParser m B.Inlines
italic :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
italic = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.emph (Inlines -> Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
DWParser m a -> (DWParser m a -> DWParser m b) -> DWParser m b
enclosed (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"//") DWParser m SourceName -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines
underlined :: PandocMonad m => DWParser m B.Inlines
underlined :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
underlined = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.underline (Inlines -> Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
DWParser m a -> (DWParser m a -> DWParser m b) -> DWParser m b
enclosed (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"__") DWParser m SourceName -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines
nowiki :: PandocMonad m => DWParser m B.Inlines
nowiki :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
nowiki = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text (Text -> Inlines)
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m (Text -> Inlines)
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"<nowiki>" ParsecT Sources ParserState m (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m SourceName
 -> ParsecT Sources ParserState m SourceName)
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"</nowiki>")
percent :: PandocMonad m => DWParser m B.Inlines
percent :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
percent = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
DWParser m a -> (DWParser m a -> DWParser m b) -> DWParser m b
enclosed (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"%%") DWParser m SourceName -> ParsecT Sources ParserState m Text
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Text
nestedText
nestedText :: (Show a, PandocMonad m)
             => DWParser m a -> DWParser m Text
nestedText :: forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Text
nestedText DWParser m a
end = ParsecT Sources ParserState m Text
innerSpace ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Column
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Column -> ParsecT s st m Char -> ParsecT s st m Text
countChar Column
1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar
  where
    innerSpace :: ParsecT Sources ParserState m Text
innerSpace = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
 -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* DWParser m a -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy DWParser m a
end
monospaced :: PandocMonad m => DWParser m B.Inlines
monospaced :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
monospaced = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.code (Text -> Inlines) -> (Inlines -> Text) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Text
T.concat ([Text] -> Text) -> (Inlines -> [Text]) -> Inlines -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Text) -> [Inline] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Inline -> Text
forall a. Walkable Inline a => a -> Text
stringify ([Inline] -> [Text]) -> (Inlines -> [Inline]) -> Inlines -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
B.toList) (Inlines -> Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
DWParser m a -> (DWParser m a -> DWParser m b) -> DWParser m b
enclosed (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"''") DWParser m SourceName -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines
subscript :: PandocMonad m => DWParser m B.Inlines
subscript :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
subscript = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.subscript (Inlines -> Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
DWParser m a
-> DWParser m b -> (DWParser m b -> DWParser m c) -> DWParser m c
between (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"<sub>") (DWParser m SourceName -> DWParser m SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (DWParser m SourceName -> DWParser m SourceName)
-> DWParser m SourceName -> DWParser m SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"</sub>") DWParser m SourceName -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines
superscript :: PandocMonad m => DWParser m B.Inlines
superscript :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
superscript = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.superscript (Inlines -> Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
DWParser m a
-> DWParser m b -> (DWParser m b -> DWParser m c) -> DWParser m c
between (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"<sup>") (DWParser m SourceName -> DWParser m SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (DWParser m SourceName -> DWParser m SourceName)
-> DWParser m SourceName -> DWParser m SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"</sup>") DWParser m SourceName -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines
deleted :: PandocMonad m => DWParser m B.Inlines
deleted :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
deleted = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.strikeout (Inlines -> Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
DWParser m a
-> DWParser m b -> (DWParser m b -> DWParser m c) -> DWParser m c
between (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"<del>") (DWParser m SourceName -> DWParser m SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (DWParser m SourceName -> DWParser m SourceName)
-> DWParser m SourceName -> DWParser m SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"</del>") DWParser m SourceName -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines
footnote :: PandocMonad m => DWParser m B.Inlines
 = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Blocks -> Inlines
B.note (Blocks -> Inlines) -> (Inlines -> Blocks) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Blocks
B.para (Inlines -> Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DWParser m SourceName
-> DWParser m SourceName
-> (DWParser m SourceName -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
DWParser m a
-> DWParser m b -> (DWParser m b -> DWParser m c) -> DWParser m c
between (SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"((") (DWParser m SourceName -> DWParser m SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (DWParser m SourceName -> DWParser m SourceName)
-> DWParser m SourceName -> DWParser m SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> DWParser m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"))") DWParser m SourceName -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
DWParser m a -> DWParser m Inlines
nestedInlines
inlineCode :: PandocMonad m => DWParser m B.Inlines
inlineCode :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inlineCode = ((Text, [Text], [(Text, Text)]) -> Text -> Inlines)
-> Text -> DWParser m Inlines
forall (m :: * -> *) a.
PandocMonad m =>
((Text, [Text], [(Text, Text)]) -> Text -> a)
-> Text -> DWParser m a
codeTag (Text, [Text], [(Text, Text)]) -> Text -> Inlines
B.codeWith Text
"code"
inlineFile :: PandocMonad m => DWParser m B.Inlines
inlineFile :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inlineFile = ((Text, [Text], [(Text, Text)]) -> Text -> Inlines)
-> Text -> DWParser m Inlines
forall (m :: * -> *) a.
PandocMonad m =>
((Text, [Text], [(Text, Text)]) -> Text -> a)
-> Text -> DWParser m a
codeTag (Text, [Text], [(Text, Text)]) -> Text -> Inlines
B.codeWith Text
"file"
inlineRaw :: PandocMonad m => DWParser m B.Inlines
inlineRaw :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inlineRaw = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ do
  Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<'
  Text
fmt <- [Text] -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
[Text] -> ParsecT s st m Text
oneOfStrings [Text
"html", Text
"php", Text
"latex"]
  
  Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>'
  Text
contents <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
                (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"</" ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string (Text -> SourceName
T.unpack Text
fmt) ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>')
  Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT Sources ParserState m Inlines)
-> Inlines -> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$
    case Text -> Text
T.toLower Text
fmt of
         Text
"php" -> Text -> Text -> Inlines
B.rawInline Text
"html" (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
"<?php " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ?>"
         Text
f -> Text -> Text -> Inlines
B.rawInline Text
f Text
contents
math :: PandocMonad m => DWParser m B.Inlines
math :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
math = (Text -> Inlines
B.displayMath (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
forall st s (m :: * -> *).
(HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
mathDisplay) ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text -> Inlines
B.math (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
forall st s (m :: * -> *).
(HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
mathInline)
makeLink :: (Text, Text) -> B.Inlines
makeLink :: (Text, Text) -> Inlines
makeLink (Text
text, Text
url) = Text -> Text -> Inlines -> Inlines
B.link Text
url Text
"" (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
text
autoEmail :: PandocMonad m => DWParser m B.Inlines
autoEmail :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
autoEmail = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ do
  ParserState
state <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState -> Bool
stateAllowLinks ParserState
state
  (Text, Text) -> Inlines
makeLink ((Text, Text) -> Inlines)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ((Text, Text) -> Inlines)
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<' ParsecT Sources ParserState m ((Text, Text) -> Inlines)
-> ParsecT Sources ParserState m (Text, Text)
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m (Text, Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (Text, Text)
emailAddress ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>'
autoLink :: PandocMonad m => DWParser m B.Inlines
autoLink :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
autoLink = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ do
  ParserState
state <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState -> Bool
stateAllowLinks ParserState
state
  (Text
text, Text
url) <- ParsecT Sources ParserState m (Text, Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (Text, Text)
uri
  Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Char -> Bool
checkLink (HasCallStack => Text -> Char
Text -> Char
T.last Text
url)
  Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT Sources ParserState m Inlines)
-> Inlines -> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ (Text, Text) -> Inlines
makeLink (Text
text, Text
url)
  where
    checkLink :: Char -> Bool
checkLink Char
c
      | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/' = Bool
True
      | Bool
otherwise = Char -> Bool
isAlphaNum Char
c
notoc :: PandocMonad m => DWParser m B.Inlines
notoc :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
notoc = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
forall a. Monoid a => a
mempty Inlines
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Inlines
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"~~NOTOC~~"
nocache :: PandocMonad m => DWParser m B.Inlines
nocache :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
nocache = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
forall a. Monoid a => a
mempty Inlines
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Inlines
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"~~NOCACHE~~"
str :: PandocMonad m => DWParser m B.Inlines
str :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
str = Text -> Inlines
B.str (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
characterReference)
symbol :: PandocMonad m => DWParser m B.Inlines
symbol :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
symbol = Text -> Inlines
B.str (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Column
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Column -> ParsecT s st m Char -> ParsecT s st m Text
countChar Column
1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar
link :: PandocMonad m => DWParser m B.Inlines
link :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
link = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ do
  ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState -> Bool
stateAllowLinks ParserState
st
  ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks :: Bool
stateAllowLinks = Bool
False }
  Inlines
l <- ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
linkText
  ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks :: Bool
stateAllowLinks = Bool
True }
  Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
l
isExternalLink :: Text -> Bool
isExternalLink :: Text -> Bool
isExternalLink Text
s = Text
"://" Text -> Text -> Bool
`T.isPrefixOf` Text
sSuff
  where
    sSuff :: Text
sSuff = (Char -> Bool) -> Text -> Text
T.dropWhile (\Char
c -> Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| (Char
c Char -> SourceName -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'-', Char
'.', Char
'+'])) Text
s
isAbsolutePath :: Text -> Bool
isAbsolutePath :: Text -> Bool
isAbsolutePath (Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'.', Text
_)) = Bool
False
isAbsolutePath Text
s = (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') Text
s
normalizeDots :: Text -> Text
normalizeDots :: Text -> Text
normalizeDots Text
path
  | Bool -> Bool
not (Text -> Bool
T.null Text
pref) = case Text -> Maybe (Char, Text)
T.uncons Text
suff of
      Just (Char
':', Text
_) -> Text
path
      Maybe (Char, Text)
_             -> Text
pref Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
suff
  | Bool
otherwise = Text
path
  where
    (Text
pref, Text
suff) = (Char -> Bool) -> Text -> (Text, Text)
T.span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') Text
path
normalizeInternalPath :: Text -> Text
normalizeInternalPath :: Text -> Text
normalizeInternalPath Text
path =
  if Text -> Bool
isAbsolutePath Text
path
    then Text -> Text
ensureAbsolute Text
normalizedPath
    else Text
normalizedPath
  where
    normalizedPath :: Text
normalizedPath = Text -> [Text] -> Text
T.intercalate Text
"/" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
".") ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
":" (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Text
normalizeDots Text
path
    ensureAbsolute :: Text -> Text
ensureAbsolute s :: Text
s@(Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'/', Text
_)) = Text
s
    ensureAbsolute Text
s = Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s
normalizePath :: Text -> Text
normalizePath :: Text -> Text
normalizePath Text
path =
  if Text -> Bool
isExternalLink Text
path
    then Text
path
    else Text -> Text
normalizeInternalPath Text
path
urlToText :: Text -> Text
urlToText :: Text -> Text
urlToText Text
url =
  if Text -> Bool
isExternalLink Text
url
    then Text
url
    else (Char -> Bool) -> Text -> Text
T.takeWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
':') Text
url
parseLink :: PandocMonad m
          => (Text -> Maybe B.Inlines -> B.Inlines)
          -> Text
          -> Text
          -> DWParser m B.Inlines
parseLink :: forall (m :: * -> *).
PandocMonad m =>
(Text -> Maybe Inlines -> Inlines)
-> Text -> Text -> DWParser m Inlines
parseLink Text -> Maybe Inlines -> Inlines
f Text
l Text
r = Text -> Maybe Inlines -> Inlines
f
  (Text -> Maybe Inlines -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (Text -> Maybe Inlines -> Inlines)
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$  Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
l
  ParsecT Sources ParserState m (Text -> Maybe Inlines -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (Maybe Inlines -> Inlines)
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|') ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Sources ParserState m Text
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
r)))
  ParsecT Sources ParserState m (Maybe Inlines -> Inlines)
-> ParsecT Sources ParserState m (Maybe Inlines)
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m (Maybe Inlines)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (Inlines -> Inlines
B.trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m [Inlines]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
 -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Text
 -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
r)))
  ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*  Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
r
splitInterwiki :: Text -> Maybe (Text, Text)
splitInterwiki :: Text -> Maybe (Text, Text)
splitInterwiki Text
path =
  case (Char -> Bool) -> Text -> (Text, Text)
T.span (\Char
c -> Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') Text
path of
    (Text
l, Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'>', Text
r)) -> (Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
Just (Text
l, Text
r)
    (Text, Text)
_ -> Maybe (Text, Text)
forall a. Maybe a
Nothing
interwikiToUrl :: Text -> Text -> Text
interwikiToUrl :: Text -> Text -> Text
interwikiToUrl Text
"callto" Text
page = Text
"callto://" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"doku" Text
page = Text
"https://www.dokuwiki.org/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"phpfn" Text
page = Text
"https://secure.php.net/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"tel" Text
page = Text
"tel:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"wp" Text
page = Text
"https://en.wikipedia.org/wiki/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"wpde" Text
page = Text
"https://de.wikipedia.org/wiki/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"wpes" Text
page = Text
"https://es.wikipedia.org/wiki/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"wpfr" Text
page = Text
"https://fr.wikipedia.org/wiki/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"wpjp" Text
page = Text
"https://jp.wikipedia.org/wiki/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
"wppl" Text
page = Text
"https://pl.wikipedia.org/wiki/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
interwikiToUrl Text
unknown Text
page = Text
unknown Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
page
linkText :: PandocMonad m => DWParser m B.Inlines
linkText :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
linkText = (Text -> Maybe Inlines -> Inlines)
-> Text -> Text -> DWParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
(Text -> Maybe Inlines -> Inlines)
-> Text -> Text -> DWParser m Inlines
parseLink Text -> Maybe Inlines -> Inlines
fromRaw Text
"[[" Text
"]]"
  where
    fromRaw :: Text -> Maybe Inlines -> Inlines
fromRaw Text
path Maybe Inlines
description =
      Text -> Text -> Inlines -> Inlines
B.link Text
normalizedPath Text
"" (Inlines -> Maybe Inlines -> Inlines
forall a. a -> Maybe a -> a
fromMaybe (Text -> Inlines
B.str Text
defaultDescription) Maybe Inlines
description)
      where
        path' :: Text
path' = Text -> Text
trim Text
path
        interwiki :: Maybe (Text, Text)
interwiki = Text -> Maybe (Text, Text)
splitInterwiki Text
path'
        normalizedPath :: Text
normalizedPath =
          case Maybe (Text, Text)
interwiki of
            Maybe (Text, Text)
Nothing -> Text -> Text
normalizePath Text
path'
            Just (Text
l, Text
r) -> Text -> Text -> Text
interwikiToUrl Text
l Text
r
        defaultDescription :: Text
defaultDescription =
          case Maybe (Text, Text)
interwiki of
            Maybe (Text, Text)
Nothing -> Text -> Text
urlToText Text
path'
            Just (Text
_, Text
r) -> Text
r
isWidthHeightParameter :: Text -> Bool
isWidthHeightParameter :: Text -> Bool
isWidthHeightParameter Text
s =
  case Text -> Maybe (Char, Text)
T.uncons Text
s of
    Just (Char
x, Text
xs) ->
      Char -> Bool
isDigit Char
x Bool -> Bool -> Bool
&& case Text -> Maybe (Char, Text)
T.uncons (Text -> Maybe (Char, Text)) -> Text -> Maybe (Char, Text)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.dropWhile Char -> Bool
isDigit Text
xs of
                     Just (Char
'x', Text
ys) | Bool -> Bool
not (Text -> Bool
T.null Text
ys) -> (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
ys
                     Maybe (Char, Text)
Nothing -> Bool
True
                     Maybe (Char, Text)
_ -> Bool
False
    Maybe (Char, Text)
_ -> Bool
False
parseWidthHeight :: Text -> (Maybe Text, Maybe Text)
parseWidthHeight :: Text -> (Maybe Text, Maybe Text)
parseWidthHeight Text
s = (Maybe Text
width, Maybe Text
height)
  where
    width :: Maybe Text
width = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.takeWhile Char -> Bool
isDigit Text
s
    height :: Maybe Text
height =
      case Text -> Maybe (Char, Text)
T.uncons (Text -> Maybe (Char, Text)) -> Text -> Maybe (Char, Text)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.dropWhile Char -> Bool
isDigit Text
s of
        Just (Char
'x', Text
xs) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
xs
        Maybe (Char, Text)
_ -> Maybe Text
forall a. Maybe a
Nothing
image :: PandocMonad m => DWParser m B.Inlines
image :: forall (m :: * -> *). PandocMonad m => DWParser m Inlines
image = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
 -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ (Text -> Maybe Inlines -> Inlines)
-> Text -> Text -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *).
PandocMonad m =>
(Text -> Maybe Inlines -> Inlines)
-> Text -> Text -> DWParser m Inlines
parseLink Text -> Maybe Inlines -> Inlines
fromRaw Text
"{{" Text
"}}"
  where
    fromRaw :: Text -> Maybe Inlines -> Inlines
fromRaw Text
path Maybe Inlines
description =
      if Bool
linkOnly
        then Text -> Text -> Inlines -> Inlines
B.link Text
normalizedPath Text
"" (Inlines -> Maybe Inlines -> Inlines
forall a. a -> Maybe a -> a
fromMaybe Inlines
defaultDescription Maybe Inlines
description)
        else (Text, [Text], [(Text, Text)])
-> Text -> Text -> Inlines -> Inlines
B.imageWith (Text
"", [Text]
classes, [(Text, Text)]
attributes) Text
normalizedPath Text
"" (Inlines -> Maybe Inlines -> Inlines
forall a. a -> Maybe a -> a
fromMaybe Inlines
defaultDescription Maybe Inlines
description)
      where
        (Text
path', Text
parameters) = (Char -> Bool) -> Text -> (Text, Text)
T.span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'?') (Text -> (Text, Text)) -> Text -> (Text, Text)
forall a b. (a -> b) -> a -> b
$ Text -> Text
trim Text
path
        normalizedPath :: Text
normalizedPath = Text -> Text
normalizePath Text
path'
        leftPadding :: Bool
leftPadding = Text
" " Text -> Text -> Bool
`T.isPrefixOf` Text
path
        rightPadding :: Bool
rightPadding = Text
" " Text -> Text -> Bool
`T.isSuffixOf` Text
path
        classes :: [Text]
classes =
          case (Bool
leftPadding, Bool
rightPadding) of
            (Bool
False, Bool
False) -> []
            (Bool
False, Bool
True) -> [Text
"align-left"]
            (Bool
True, Bool
False) -> [Text
"align-right"]
            (Bool
True, Bool
True) -> [Text
"align-center"]
        parameterList :: [Text]
parameterList = HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
"&" (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Column -> Text -> Text
T.drop Column
1 Text
parameters
        linkOnly :: Bool
linkOnly = Text
"linkonly" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
parameterList
        (Maybe Text
width, Maybe Text
height) = (Maybe Text, Maybe Text)
-> (Text -> (Maybe Text, Maybe Text))
-> Maybe Text
-> (Maybe Text, Maybe Text)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe Text
forall a. Maybe a
Nothing, Maybe Text
forall a. Maybe a
Nothing) Text -> (Maybe Text, Maybe Text)
parseWidthHeight ((Text -> Bool) -> [Text] -> Maybe Text
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
F.find Text -> Bool
isWidthHeightParameter [Text]
parameterList)
        attributes :: [(Text, Text)]
attributes = [Maybe (Text, Text)] -> [(Text, Text)]
forall a. [Maybe a] -> [a]
catMaybes [(Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text
"width",) Maybe Text
width, (Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text
"height",) Maybe Text
height]
        defaultDescription :: Inlines
defaultDescription = Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text
urlToText Text
path'
block :: PandocMonad m => DWParser m B.Blocks
block :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
block = do
  Blocks
res <- Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT Sources ParserState m () -> DWParser m Blocks
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
         DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockElements
         DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
para
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
  Text -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => Text -> m ()
trace (Column -> Text -> Text
T.take Column
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 -> DWParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res
blockElements :: PandocMonad m => DWParser m B.Blocks
blockElements :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockElements = DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
horizontalLine
            DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
header
            DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => Text -> DWParser m Blocks
list Text
"  "
            DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
indentedCode
            DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
quote
            DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockCode
            DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockFile
            DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockRaw
            DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
table
horizontalLine :: PandocMonad m => DWParser m B.Blocks
horizontalLine :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
horizontalLine = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks
B.horizontalRule Blocks
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Blocks
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"---" ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-') ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
eol
header :: PandocMonad m => DWParser m B.Blocks
 = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ do
  DWParser m ()
forall (m :: * -> *). PandocMonad m => DWParser m ()
guardColumnOne
  SourceName
eqs <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'=')
  let lev :: Column
lev = SourceName -> Column
forall a. [a] -> Column
forall (t :: * -> *) a. Foldable t => t a -> Column
length SourceName
eqs
  Bool -> DWParser m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> DWParser m ()) -> Bool -> DWParser m ()
forall a b. (a -> b) -> a -> b
$ Column
lev Column -> Column -> Bool
forall a. Ord a => a -> a -> Bool
< Column
7
  Inlines
contents <- Inlines -> Inlines
B.trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline (ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m SourceName
 -> ParsecT Sources ParserState m SourceName)
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'=' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'='))
  (Text, [Text], [(Text, Text)])
attr <- (Text, [Text], [(Text, Text)])
-> Inlines
-> ParsecT Sources ParserState m (Text, [Text], [(Text, Text)])
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
 HasIdentifierList st) =>
(Text, [Text], [(Text, Text)])
-> Inlines -> ParsecT s st m (Text, [Text], [(Text, Text)])
registerHeader (Text, [Text], [(Text, Text)])
nullAttr Inlines
contents
  Blocks -> ParsecT Sources ParserState m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources ParserState m Blocks)
-> Blocks -> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ (Text, [Text], [(Text, Text)]) -> Column -> Inlines -> Blocks
B.headerWith (Text, [Text], [(Text, Text)])
attr (Column
7 Column -> Column -> Column
forall a. Num a => a -> a -> a
- Column
lev) Inlines
contents
list :: PandocMonad m => Text -> DWParser m B.Blocks
list :: forall (m :: * -> *). PandocMonad m => Text -> DWParser m Blocks
list Text
prefix = Text -> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => Text -> DWParser m Blocks
bulletList Text
prefix DWParser m Blocks -> DWParser m Blocks -> DWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> DWParser m Blocks
forall (m :: * -> *). PandocMonad m => Text -> DWParser m Blocks
orderedList Text
prefix
bulletList :: PandocMonad m => Text -> DWParser m B.Blocks
bulletList :: forall (m :: * -> *). PandocMonad m => Text -> DWParser m Blocks
bulletList Text
prefix = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
B.bulletList ([Blocks] -> Blocks)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Char -> ParsecT Sources ParserState m [Blocks]
forall (m :: * -> *).
PandocMonad m =>
Text -> Char -> DWParser m [Blocks]
parseList Text
prefix Char
'*'
orderedList :: PandocMonad m => Text -> DWParser m B.Blocks
orderedList :: forall (m :: * -> *). PandocMonad m => Text -> DWParser m Blocks
orderedList Text
prefix = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
B.orderedList ([Blocks] -> Blocks)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Char -> ParsecT Sources ParserState m [Blocks]
forall (m :: * -> *).
PandocMonad m =>
Text -> Char -> DWParser m [Blocks]
parseList Text
prefix Char
'-'
parseList :: PandocMonad m
          => Text
          -> Char
          -> DWParser m [B.Blocks]
parseList :: forall (m :: * -> *).
PandocMonad m =>
Text -> Char -> DWParser m [Blocks]
parseList Text
prefix Char
marker =
  ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
(<>) (Blocks -> Blocks -> Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m (Blocks -> Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Blocks
item ParsecT Sources ParserState m (Blocks -> Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([Blocks] -> Blocks)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Blocks
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat (ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Blocks
continuation))
  where
    continuation :: ParsecT Sources ParserState m Blocks
continuation = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> DWParser m Blocks
list (Text
"  " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
prefix)
    item :: ParsecT Sources ParserState m Blocks
item = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
prefix ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
marker ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' ' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Blocks
itemContents
    itemContents :: ParsecT Sources ParserState m Blocks
itemContents = Inlines -> Blocks
B.plain (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Blocks)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline' ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
eol
indentedCode :: PandocMonad m => DWParser m B.Blocks
indentedCode :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
indentedCode = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Blocks
B.codeBlock (Text -> Blocks) -> ([Text] -> Text) -> [Text] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines ([Text] -> Blocks)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Text
forall {u}. ParsecT Sources u m Text
indentedLine
 where
   indentedLine :: ParsecT Sources u m Text
indentedLine = 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 (ParsecT Sources u m Text -> ParsecT Sources u m Text)
-> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT Sources u m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"  " ParsecT Sources u m SourceName
-> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
eol
quote :: PandocMonad m => DWParser m B.Blocks
quote :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
quote = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Column -> ParsecT Sources ParserState m Blocks
nestedQuote Column
0
  where
    prefix :: Column -> ParsecT s u m SourceName
prefix Column
level = Column -> ParsecT s u m Char -> ParsecT s u m SourceName
forall s (m :: * -> *) t u a.
Stream s m t =>
Column -> ParsecT s u m a -> ParsecT s u m [a]
count Column
level (Char -> ParsecT s u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>')
    contents :: Column -> ParsecT Sources ParserState m Blocks
contents Column
level = Column -> ParsecT Sources ParserState m Blocks
nestedQuote Column
level ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Blocks
quoteLine
    quoteLine :: ParsecT Sources ParserState m Blocks
quoteLine = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.plain (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
B.trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Blocks)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline' ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
eol
    quoteContents :: Column -> ParsecT Sources ParserState m Blocks
quoteContents Column
level = Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
(<>) (Blocks -> Blocks -> Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m (Blocks -> Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Column -> ParsecT Sources ParserState m Blocks
contents Column
level ParsecT Sources ParserState m (Blocks -> Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Column -> ParsecT Sources ParserState m Blocks
quoteContinuation Column
level
    quoteContinuation :: Column -> ParsecT Sources ParserState m Blocks
quoteContinuation Column
level = [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Column -> ParsecT Sources ParserState m SourceName
forall {m :: * -> *} {s} {u}.
(Stream s m Char, UpdateSourcePos s Char) =>
Column -> ParsecT s u m SourceName
prefix Column
level ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Column -> ParsecT Sources ParserState m Blocks
contents Column
level)
    nestedQuote :: Column -> ParsecT Sources ParserState m Blocks
nestedQuote Column
level = Blocks -> Blocks
B.blockQuote (Blocks -> Blocks)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m (Blocks -> Blocks)
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>' ParsecT Sources ParserState m (Blocks -> Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m (a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Column -> ParsecT Sources ParserState m Blocks
quoteContents (Column
level Column -> Column -> Column
forall a. Num a => a -> a -> a
+ Column
1 :: Int)
blockRaw :: PandocMonad m => DWParser m B.Blocks
blockRaw :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockRaw = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
 -> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ do
  Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<'
  Text
fmt <- [Text] -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
[Text] -> ParsecT s st m Text
oneOfStrings [Text
"HTML", Text
"PHP", Text
"LATEX"]
  
  Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>'
  ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m SourceName
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 ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
eol)
  Text
contents <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
               (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string SourceName
"</" ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m SourceName
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> SourceName -> ParsecT Sources ParserState m SourceName
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
SourceName -> ParsecT s u m SourceName
string (Text -> SourceName
T.unpack Text
fmt) ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>')
  Blocks -> ParsecT Sources ParserState m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources ParserState m Blocks)
-> Blocks -> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$
    case Text -> Text
T.toLower Text
fmt of
         Text
"php" -> Text -> Text -> Blocks
B.rawBlock Text
"html" (Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$ Text
"<?php " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ?>"
         Text
f -> Text -> Text -> Blocks
B.rawBlock Text
f Text
contents
table :: PandocMonad m => DWParser m B.Blocks
table :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
table = do
  Char
firstSeparator <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => DWParser m Char
tableCellSeparator
  [[(Alignment, Blocks)]]
rows <- DWParser m [[(Alignment, Blocks)]]
forall (m :: * -> *).
PandocMonad m =>
DWParser m [[(Alignment, Blocks)]]
tableRows
  let firstRow :: [(Alignment, Blocks)]
firstRow = [(Alignment, Blocks)]
-> Maybe [(Alignment, Blocks)] -> [(Alignment, Blocks)]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [(Alignment, Blocks)] -> [(Alignment, Blocks)])
-> ([[(Alignment, Blocks)]] -> Maybe [(Alignment, Blocks)])
-> [[(Alignment, Blocks)]]
-> [(Alignment, Blocks)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[(Alignment, Blocks)]] -> Maybe [(Alignment, Blocks)]
forall a. [a] -> Maybe a
Safe.headMay ([[(Alignment, Blocks)]] -> [(Alignment, Blocks)])
-> [[(Alignment, Blocks)]] -> [(Alignment, Blocks)]
forall a b. (a -> b) -> a -> b
$ [[(Alignment, Blocks)]]
rows
  let ([(Alignment, Blocks)]
headerRow, [[(Alignment, Blocks)]]
body) = if Char
firstSeparator Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'^'
                            then ([(Alignment, Blocks)]
firstRow, [[(Alignment, Blocks)]] -> [[(Alignment, Blocks)]]
forall a. HasCallStack => [a] -> [a]
tail [[(Alignment, Blocks)]]
rows)
                            else ([], [[(Alignment, Blocks)]]
rows)
  
  
  
  
  let attrs :: [(Alignment, ColWidth)]
attrs =  ((Alignment, Blocks) -> (Alignment, ColWidth))
-> [(Alignment, Blocks)] -> [(Alignment, ColWidth)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Alignment
a, Blocks
_) -> (Alignment
a, ColWidth
ColWidthDefault)) [(Alignment, Blocks)]
firstRow
  let toRow :: [Blocks] -> Row
toRow = (Text, [Text], [(Text, Text)]) -> [Cell] -> Row
Row (Text, [Text], [(Text, Text)])
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 a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Blocks]
l)]
  Blocks -> DWParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> DWParser m Blocks) -> Blocks -> DWParser m Blocks
forall a b. (a -> b) -> a -> b
$ Caption
-> [(Alignment, ColWidth)]
-> TableHead
-> [TableBody]
-> TableFoot
-> Blocks
B.table Caption
B.emptyCaption
                 [(Alignment, ColWidth)]
attrs
                 ((Text, [Text], [(Text, Text)]) -> [Row] -> TableHead
TableHead (Text, [Text], [(Text, Text)])
nullAttr ([Row] -> TableHead) -> [Row] -> TableHead
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Row]
toHeaderRow (((Alignment, Blocks) -> Blocks)
-> [(Alignment, Blocks)] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map (Alignment, Blocks) -> Blocks
forall a b. (a, b) -> b
snd [(Alignment, Blocks)]
headerRow))
                 [(Text, [Text], [(Text, Text)])
-> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody (Text, [Text], [(Text, Text)])
nullAttr RowHeadColumns
0 [] ([Row] -> TableBody) -> [Row] -> TableBody
forall a b. (a -> b) -> a -> b
$ ([(Alignment, Blocks)] -> Row) -> [[(Alignment, Blocks)]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map ([Blocks] -> Row
toRow ([Blocks] -> Row)
-> ([(Alignment, Blocks)] -> [Blocks])
-> [(Alignment, Blocks)]
-> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((Alignment, Blocks) -> Blocks)
-> [(Alignment, Blocks)] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map (Alignment, Blocks) -> Blocks
forall a b. (a, b) -> b
snd)) [[(Alignment, Blocks)]]
body]
                 ((Text, [Text], [(Text, Text)]) -> [Row] -> TableFoot
TableFoot (Text, [Text], [(Text, Text)])
nullAttr [])
tableRows :: PandocMonad m => DWParser m [[(Alignment, B.Blocks)]]
tableRows :: forall (m :: * -> *).
PandocMonad m =>
DWParser m [[(Alignment, Blocks)]]
tableRows = ParsecT Sources ParserState m [(Alignment, Blocks)]
-> ParsecT Sources ParserState m [[(Alignment, Blocks)]]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m [(Alignment, Blocks)]
forall (m :: * -> *).
PandocMonad m =>
DWParser m [(Alignment, Blocks)]
tableRow
tableRow :: PandocMonad m => DWParser m [(Alignment, B.Blocks)]
tableRow :: forall (m :: * -> *).
PandocMonad m =>
DWParser m [(Alignment, Blocks)]
tableRow = ParsecT Sources ParserState m (Alignment, Blocks)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [(Alignment, Blocks)]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m (Alignment, Blocks)
forall (m :: * -> *).
PandocMonad m =>
DWParser m (Alignment, Blocks)
tableCell ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => DWParser m Char
tableRowEnd
tableRowEnd :: PandocMonad m => DWParser m Char
tableRowEnd :: forall (m :: * -> *). PandocMonad m => DWParser m Char
tableRowEnd = ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => DWParser m Char
tableCellSeparator ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m SourceName
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m SourceName
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 ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
eol
tableCellSeparator :: PandocMonad m => DWParser m Char
tableCellSeparator :: forall (m :: * -> *). PandocMonad m => DWParser m Char
tableCellSeparator = Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'^'
tableCell :: PandocMonad m => DWParser m (Alignment, B.Blocks)
tableCell :: forall (m :: * -> *).
PandocMonad m =>
DWParser m (Alignment, Blocks)
tableCell = ParsecT Sources ParserState m (Alignment, Blocks)
-> ParsecT Sources ParserState m (Alignment, Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Alignment, Blocks)
 -> ParsecT Sources ParserState m (Alignment, Blocks))
-> ParsecT Sources ParserState m (Alignment, Blocks)
-> ParsecT Sources ParserState m (Alignment, Blocks)
forall a b. (a -> b) -> a -> b
$ (([Inlines] -> Blocks)
-> (Alignment, [Inlines]) -> (Alignment, Blocks)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Inlines -> Blocks
B.plain (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
B.trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat)) ((Alignment, [Inlines]) -> (Alignment, Blocks))
-> ParsecT Sources ParserState m (Alignment, [Inlines])
-> ParsecT Sources ParserState m (Alignment, Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Alignment, [Inlines])
cellContent
  where
    cellContent :: ParsecT Sources ParserState m (Alignment, [Inlines])
cellContent = do
      
      
      DWParser m Char
forall (m :: * -> *). PandocMonad m => DWParser m Char
tableCellSeparator
      [Inlines]
cellInline <- ParsecT Sources ParserState m Inlines
-> DWParser m Char -> ParsecT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inlineUnconsolidatedWhitespace (DWParser m Char -> DWParser m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead DWParser m Char
forall (m :: * -> *). PandocMonad m => DWParser m Char
tableCellSeparator)
      let left :: Bool
left  = [Inlines
B.space, Inlines
B.space] [Inlines] -> [Inlines] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` [Inlines]
cellInline
      let right :: Bool
right = [Inlines
B.space, Inlines
B.space] [Inlines] -> [Inlines] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` [Inlines]
cellInline
      let alignment :: Alignment
alignment = case (Bool
left, Bool
right) of
                           (Bool
True, Bool
True)   -> Alignment
AlignCenter
                           (Bool
True, Bool
False)  -> Alignment
AlignRight
                           (Bool
False, Bool
True)  -> Alignment
AlignLeft
                           (Bool
False, Bool
False) -> Alignment
AlignDefault
      (Alignment, [Inlines])
-> ParsecT Sources ParserState m (Alignment, [Inlines])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Alignment
alignment, [Inlines]
cellInline)
blockCode :: PandocMonad m => DWParser m B.Blocks
blockCode :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockCode = ((Text, [Text], [(Text, Text)]) -> Text -> Blocks)
-> Text -> DWParser m Blocks
forall (m :: * -> *) a.
PandocMonad m =>
((Text, [Text], [(Text, Text)]) -> Text -> a)
-> Text -> DWParser m a
codeTag (Text, [Text], [(Text, Text)]) -> Text -> Blocks
B.codeBlockWith Text
"code"
blockFile :: PandocMonad m => DWParser m B.Blocks
blockFile :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockFile = ((Text, [Text], [(Text, Text)]) -> Text -> Blocks)
-> Text -> DWParser m Blocks
forall (m :: * -> *) a.
PandocMonad m =>
((Text, [Text], [(Text, Text)]) -> Text -> a)
-> Text -> DWParser m a
codeTag (Text, [Text], [(Text, Text)]) -> Text -> Blocks
B.codeBlockWith Text
"file"
para :: PandocMonad m => DWParser m B.Blocks
para :: forall (m :: * -> *). PandocMonad m => DWParser m Blocks
para = Inlines -> Blocks
result (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Blocks)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => DWParser m Inlines
inline ParsecT Sources ParserState m ()
endOfParaElement
 where
   endOfParaElement :: ParsecT Sources ParserState m ()
endOfParaElement = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m ()
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
endOfInput ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
endOfPara ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
newBlockElement
   endOfInput :: ParsecT Sources u m ()
endOfInput       = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
   endOfPara :: ParsecT Sources u m ()
endOfPara        = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
   newBlockElement :: ParsecT Sources ParserState m ()
newBlockElement  = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => DWParser m Blocks
blockElements
   result :: Inlines -> Blocks
result Inlines
content   = if (Inline -> Bool) -> Inlines -> 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) Inlines
content
                      then Blocks
forall a. Monoid a => a
mempty
                      else Inlines -> Blocks
B.para (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.trimInlines Inlines
content