{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.TWiki ( readTWiki
) where
import Control.Monad
import Control.Monad.Except (throwError)
import Data.Char (isAlphaNum)
import qualified Data.Foldable as F
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Text.HTML.TagSoup
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.Readers.HTML (htmlTag, isCommentTag)
import Text.Pandoc.Shared (tshow)
import Text.Pandoc.XML (fromEntities)
readTWiki :: (PandocMonad m, ToSources a)
=> ReaderOptions
-> a
-> m Pandoc
readTWiki :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readTWiki ReaderOptions
opts a
s = do
let sources :: Sources
sources = Int -> Sources -> Sources
ensureFinalNewlines Int
2 (a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s)
Either PandocError Pandoc
res <- ParsecT Sources ParserState m Pandoc
-> ParserState -> Sources -> m (Either PandocError Pandoc)
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParsecT Sources ParserState m Pandoc
forall (m :: * -> *). PandocMonad m => TWParser m Pandoc
parseTWiki ParserState
forall a. Default a => a
def{ stateOptions = opts } Sources
sources
case Either PandocError Pandoc
res of
Left PandocError
e -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
Right Pandoc
d -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
d
type TWParser = ParsecT Sources ParserState
tryMsg :: Text -> TWParser m a -> TWParser m a
tryMsg :: forall (m :: * -> *) a. Text -> TWParser m a -> TWParser m a
tryMsg Text
msg TWParser m a
p = TWParser m a -> TWParser m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try TWParser m a
p TWParser m a -> String -> TWParser m a
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> Text -> String
T.unpack Text
msg
htmlElement :: PandocMonad m => Text -> TWParser m (Attr, Text)
htmlElement :: forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m (Attr, Text)
htmlElement Text
tag = Text -> TWParser m (Attr, Text) -> TWParser m (Attr, Text)
forall (m :: * -> *) a. Text -> TWParser m a -> TWParser m a
tryMsg Text
tag (TWParser m (Attr, Text) -> TWParser m (Attr, Text))
-> TWParser m (Attr, Text) -> TWParser m (Attr, Text)
forall a b. (a -> b) -> a -> b
$ do
(TagOpen Text
_ [Attribute Text]
attr, Text
_) <- (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> [Attribute Text] -> Tag Text
forall str. str -> [Attribute str] -> Tag str
TagOpen Text
tag [])
Text
content <- String -> Text
T.pack (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources 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 ()
endtag 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 ()
endofinput)
(Attr, Text) -> TWParser m (Attr, Text)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Attribute Text] -> Attr
htmlAttrToPandoc [Attribute Text]
attr, Text -> Text
trim Text
content)
where
endtag :: ParsecT Sources ParserState m ()
endtag = ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag (Tag Text -> Tag Text -> Bool
forall str t. (StringLike str, TagRep t) => Tag str -> t -> Bool
~== Text -> Tag Text
forall str. str -> Tag str
TagClose Text
tag)
endofinput :: ParsecT Sources u m ()
endofinput = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ 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
trim :: Text -> Text
trim = (Char -> Bool) -> Text -> Text
T.dropAround (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'\n')
htmlAttrToPandoc :: [Attribute Text] -> Attr
htmlAttrToPandoc :: [Attribute Text] -> Attr
htmlAttrToPandoc [Attribute Text]
attrs = (Text
ident, [Text]
classes, [Attribute Text]
keyvals)
where
ident :: Text
ident = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"id" [Attribute Text]
attrs
classes :: [Text]
classes = [Text] -> (Text -> [Text]) -> Maybe Text -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Text -> [Text]
T.words (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Attribute Text]
attrs
keyvals :: [Attribute Text]
keyvals = [(Text
k,Text
v) | (Text
k,Text
v) <- [Attribute Text]
attrs, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"id" Bool -> Bool -> Bool
&& Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"class"]
parseHtmlContentWithAttrs :: PandocMonad m
=> Text -> TWParser m a -> TWParser m (Attr, [a])
parseHtmlContentWithAttrs :: forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m (Attr, [a])
parseHtmlContentWithAttrs Text
tag TWParser m a
parser = do
(Attr
attr, Text
content) <- Text -> TWParser m (Attr, Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m (Attr, Text)
htmlElement Text
tag
[a]
parsedContent <- 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 -> ParsecT Sources ParserState m [a]
parseContent Text
content
(Attr, [a]) -> TWParser m (Attr, [a])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Attr
attr, [a]
parsedContent)
where
parseContent :: Text -> ParsecT Sources ParserState m [a]
parseContent = ParsecT Sources ParserState m [a]
-> Text -> ParsecT Sources ParserState m [a]
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' (ParsecT Sources ParserState m [a]
-> Text -> ParsecT Sources ParserState m [a])
-> ParsecT Sources ParserState m [a]
-> Text
-> ParsecT Sources ParserState m [a]
forall a b. (a -> b) -> a -> b
$ TWParser m a
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [a]
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 TWParser m a
parser ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
endOfContent
endOfContent :: ParsecT Sources u m ()
endOfContent = 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
parseCharHtmlContentWithAttrs :: PandocMonad m
=> Text -> TWParser m Char -> TWParser m (Attr, Text)
parseCharHtmlContentWithAttrs :: forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m Char -> TWParser m (Attr, Text)
parseCharHtmlContentWithAttrs Text
tag = ((Attr, String) -> (Attr, Text))
-> ParsecT Sources ParserState m (Attr, String)
-> ParsecT Sources ParserState m (Attr, Text)
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr, String) -> (Attr, Text)
forall {a}. (a, String) -> (a, Text)
go (ParsecT Sources ParserState m (Attr, String)
-> ParsecT Sources ParserState m (Attr, Text))
-> (TWParser m Char
-> ParsecT Sources ParserState m (Attr, String))
-> TWParser m Char
-> ParsecT Sources ParserState m (Attr, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text
-> TWParser m Char -> ParsecT Sources ParserState m (Attr, String)
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m (Attr, [a])
parseHtmlContentWithAttrs Text
tag
where
go :: (a, String) -> (a, Text)
go (a
x, String
y) = (a
x, String -> Text
T.pack String
y)
parseHtmlContent :: PandocMonad m => Text -> TWParser m a -> TWParser m [a]
parseHtmlContent :: forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m [a]
parseHtmlContent Text
tag TWParser m a
p = (Attr, [a]) -> [a]
forall a b. (a, b) -> b
snd ((Attr, [a]) -> [a])
-> ParsecT Sources ParserState m (Attr, [a])
-> ParsecT Sources ParserState m [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> TWParser m a -> ParsecT Sources ParserState m (Attr, [a])
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m (Attr, [a])
parseHtmlContentWithAttrs Text
tag TWParser m a
p
parseTWiki :: PandocMonad m => TWParser m Pandoc
parseTWiki :: forall (m :: * -> *). PandocMonad m => TWParser m Pandoc
parseTWiki =
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 => TWParser 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
block :: PandocMonad m => TWParser m B.Blocks
block :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
block = do
Blocks
res <- Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT Sources ParserState m () -> TWParser 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
TWParser m Blocks -> TWParser m Blocks -> TWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TWParser m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
blockElements
TWParser m Blocks -> TWParser m Blocks -> TWParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TWParser m Blocks
forall (m :: * -> *). PandocMonad m => TWParser 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 (Int -> Text -> Text
T.take Int
60 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Block] -> Text
forall a. Show a => a -> Text
tshow ([Block] -> Text) -> [Block] -> Text
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
res)
Blocks -> TWParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res
blockElements :: PandocMonad m => TWParser m B.Blocks
blockElements :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
blockElements = [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
choice [ ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
separator
, ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
header
, ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
verbatim
, ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
literal
, Text -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
list Text
""
, ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
table
, ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
blockQuote
, ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
noautolink
]
separator :: PandocMonad m => TWParser m B.Blocks
separator :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
separator = Text -> TWParser m Blocks -> TWParser m Blocks
forall (m :: * -> *) a. Text -> TWParser m a -> TWParser m a
tryMsg Text
"separator" (TWParser m Blocks -> TWParser m Blocks)
-> TWParser m Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"---" ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> TWParser m Blocks -> TWParser m Blocks
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> TWParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
B.horizontalRule
header :: PandocMonad m => TWParser m B.Blocks
= Text -> TWParser m Blocks -> TWParser m Blocks
forall (m :: * -> *) a. Text -> TWParser m a -> TWParser m a
tryMsg Text
"header" (TWParser m Blocks -> TWParser m Blocks)
-> TWParser m Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"---"
Int
level <- String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String -> Int)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
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
'+')
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
$ Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
6
[Text]
classes <- [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 [] (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
$ String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"!!" ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Text] -> ParsecT Sources ParserState m [Text]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text
"unnumbered"]
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Inlines
content <- 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 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 => TWParser m Inlines
inline ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
Attr
attr <- Attr -> Inlines -> ParsecT Sources ParserState m Attr
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
HasIdentifierList st) =>
Attr -> Inlines -> ParsecT s st m Attr
registerHeader (Text
"", [Text]
classes, []) Inlines
content
Blocks -> TWParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TWParser m Blocks) -> Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Inlines -> Blocks
B.headerWith Attr
attr Int
level Inlines
content
verbatim :: PandocMonad m => TWParser m B.Blocks
verbatim :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
verbatim = (Attr -> Text -> Blocks) -> (Attr, Text) -> Blocks
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Attr -> Text -> Blocks
B.codeBlockWith ((Attr, Text) -> Blocks)
-> ParsecT Sources ParserState m (Attr, Text)
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> ParsecT Sources ParserState m (Attr, Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m (Attr, Text)
htmlElement Text
"verbatim" ParsecT Sources ParserState m (Attr, Text)
-> ParsecT Sources ParserState m (Attr, Text)
-> ParsecT Sources ParserState m (Attr, Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> ParsecT Sources ParserState m (Attr, Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m (Attr, Text)
htmlElement Text
"pre")
literal :: PandocMonad m => TWParser m B.Blocks
literal :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
literal = (Attr, Text) -> Blocks
forall {a} {a} {b}.
(Eq a, IsString a) =>
((a, b, [(a, Text)]), Text) -> Blocks
rawBlock ((Attr, Text) -> Blocks)
-> ParsecT Sources ParserState m (Attr, Text)
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT Sources ParserState m (Attr, Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m (Attr, Text)
htmlElement Text
"literal"
where
format :: (a, b, [(a, a)]) -> a
format (a
_, b
_, [(a, a)]
kvs) = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
"html" (Maybe a -> a) -> Maybe a -> a
forall a b. (a -> b) -> a -> b
$ a -> [(a, a)] -> Maybe a
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup a
"format" [(a, a)]
kvs
rawBlock :: ((a, b, [(a, Text)]), Text) -> Blocks
rawBlock ((a, b, [(a, Text)])
attrs, Text
content) = Text -> Text -> Blocks
B.rawBlock ((a, b, [(a, Text)]) -> Text
forall {a} {a} {a} {b}.
(Eq a, IsString a, IsString a) =>
(a, b, [(a, a)]) -> a
format (a, b, [(a, Text)])
attrs) Text
content
list :: PandocMonad m => Text -> TWParser m B.Blocks
list :: forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
list Text
prefix = [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
choice [ Text -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
bulletList Text
prefix
, Text -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
orderedList Text
prefix
, Text -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
definitionList Text
prefix]
definitionList :: PandocMonad m => Text -> TWParser m B.Blocks
definitionList :: forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
definitionList Text
prefix = Text -> TWParser m Blocks -> TWParser m Blocks
forall (m :: * -> *) a. Text -> TWParser m a -> TWParser m a
tryMsg Text
"definitionList" (TWParser m Blocks -> TWParser m Blocks)
-> TWParser m Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
[Text]
indent <- 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
prefix ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
" ") ParsecT Sources ParserState m [Text]
-> 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 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
"$ "
[(Inlines, [Blocks])]
elements <- ParsecT Sources ParserState m (Inlines, [Blocks])
-> ParsecT Sources ParserState m [(Inlines, [Blocks])]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m (Inlines, [Blocks])
-> ParsecT Sources ParserState m [(Inlines, [Blocks])])
-> ParsecT Sources ParserState m (Inlines, [Blocks])
-> ParsecT Sources ParserState m [(Inlines, [Blocks])]
forall a b. (a -> b) -> a -> b
$ Text -> ParsecT Sources ParserState m (Inlines, [Blocks])
forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m (Inlines, [Blocks])
parseDefinitionListItem (Text
prefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.concat [Text]
indent)
Blocks -> TWParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TWParser m Blocks) -> Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$ [(Inlines, [Blocks])] -> Blocks
B.definitionList [(Inlines, [Blocks])]
elements
where
parseDefinitionListItem :: PandocMonad m
=> Text -> TWParser m (B.Inlines, [B.Blocks])
parseDefinitionListItem :: forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m (Inlines, [Blocks])
parseDefinitionListItem Text
indent = do
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
indent Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"$ ") ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
[Inlines]
term <- ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m String
-> 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 => TWParser m Inlines
inline (ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m [Inlines])
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m [Inlines]
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
": "
Blocks
line <- Text -> ParsecT Sources ParserState m String -> TWParser m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Show a) =>
Text -> TWParser m a -> TWParser m Blocks
listItemLine Text
indent (ParsecT Sources ParserState m String -> TWParser m Blocks)
-> ParsecT Sources ParserState m String -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"$ "
(Inlines, [Blocks]) -> TWParser m (Inlines, [Blocks])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat [Inlines]
term, [Blocks
line])
bulletList :: PandocMonad m => Text -> TWParser m B.Blocks
bulletList :: forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
bulletList Text
prefix = Text -> TWParser m Blocks -> TWParser m Blocks
forall (m :: * -> *) a. Text -> TWParser m a -> TWParser m a
tryMsg Text
"bulletList" (TWParser m Blocks -> TWParser m Blocks)
-> TWParser m Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$
Text -> TWParser m Char -> TWParser m Char -> TWParser m Blocks
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m Char -> TWParser m a -> TWParser m Blocks
parseList Text
prefix (Char -> TWParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*') (Char -> TWParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' ')
orderedList :: PandocMonad m => Text -> TWParser m B.Blocks
orderedList :: forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
orderedList Text
prefix = Text -> TWParser m Blocks -> TWParser m Blocks
forall (m :: * -> *) a. Text -> TWParser m a -> TWParser m a
tryMsg Text
"orderedList" (TWParser m Blocks -> TWParser m Blocks)
-> TWParser m Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$
Text -> TWParser m Char -> TWParser m String -> TWParser m Blocks
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m Char -> TWParser m a -> TWParser m Blocks
parseList Text
prefix (String -> TWParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
oneOf String
"1iIaA") (String -> TWParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
". ")
parseList :: PandocMonad m
=> Text -> TWParser m Char -> TWParser m a -> TWParser m B.Blocks
parseList :: forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m Char -> TWParser m a -> TWParser m Blocks
parseList Text
prefix TWParser m Char
marker TWParser m a
delim = do
(Text
indent, Char
style) <- ParsecT Sources ParserState m (Text, Char)
-> ParsecT Sources ParserState m (Text, 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 (Text, Char)
-> ParsecT Sources ParserState m (Text, Char))
-> ParsecT Sources ParserState m (Text, Char)
-> ParsecT Sources ParserState m (Text, Char)
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 (Text, Char)
-> ParsecT Sources ParserState m (Text, 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
*> ParsecT Sources ParserState m (Text, Char)
listStyle ParsecT Sources ParserState m (Text, Char)
-> TWParser m a -> ParsecT Sources ParserState m (Text, 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
<* TWParser m a
delim
[Blocks]
blocks <- TWParser m Blocks -> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (TWParser m Blocks -> ParsecT Sources ParserState m [Blocks])
-> TWParser m Blocks -> ParsecT Sources ParserState m [Blocks]
forall a b. (a -> b) -> a -> b
$ Text -> TWParser m Char -> TWParser m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Show a) =>
Text -> TWParser m a -> TWParser m Blocks
parseListItem (Text
prefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
indent) (Char -> TWParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
style TWParser m Char -> TWParser m a -> TWParser 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
<* TWParser m a
delim)
Blocks -> TWParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TWParser m Blocks) -> Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$ case Char
style of
Char
'1' -> ListAttributes -> [Blocks] -> Blocks
B.orderedListWith (Int
1, ListNumberStyle
DefaultStyle, ListNumberDelim
DefaultDelim) [Blocks]
blocks
Char
'i' -> ListAttributes -> [Blocks] -> Blocks
B.orderedListWith (Int
1, ListNumberStyle
LowerRoman, ListNumberDelim
DefaultDelim) [Blocks]
blocks
Char
'I' -> ListAttributes -> [Blocks] -> Blocks
B.orderedListWith (Int
1, ListNumberStyle
UpperRoman, ListNumberDelim
DefaultDelim) [Blocks]
blocks
Char
'a' -> ListAttributes -> [Blocks] -> Blocks
B.orderedListWith (Int
1, ListNumberStyle
LowerAlpha, ListNumberDelim
DefaultDelim) [Blocks]
blocks
Char
'A' -> ListAttributes -> [Blocks] -> Blocks
B.orderedListWith (Int
1, ListNumberStyle
UpperAlpha, ListNumberDelim
DefaultDelim) [Blocks]
blocks
Char
_ -> [Blocks] -> Blocks
B.bulletList [Blocks]
blocks
where
listStyle :: ParsecT Sources ParserState m (Text, Char)
listStyle = do
[Text]
indent <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text])
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall a b. (a -> b) -> a -> b
$ 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
" "
Char
style <- TWParser m Char
marker
(Text, Char) -> ParsecT Sources ParserState m (Text, Char)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> Text
T.concat [Text]
indent, Char
style)
parseListItem :: (PandocMonad m, Show a)
=> Text -> TWParser m a -> TWParser m B.Blocks
parseListItem :: forall (m :: * -> *) a.
(PandocMonad m, Show a) =>
Text -> TWParser m a -> TWParser m Blocks
parseListItem Text
prefix TWParser m a
marker = 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 -> TWParser m a -> TWParser m a
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
>> TWParser m a
marker TWParser m a
-> 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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> TWParser m a -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Show a) =>
Text -> TWParser m a -> TWParser m Blocks
listItemLine Text
prefix TWParser m a
marker
listItemLine :: (PandocMonad m, Show a)
=> Text -> TWParser m a -> TWParser m B.Blocks
listItemLine :: forall (m :: * -> *) a.
(PandocMonad m, Show a) =>
Text -> TWParser m a -> TWParser m Blocks
listItemLine Text
prefix TWParser m a
marker = [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 Text
lineContent ParsecT Sources ParserState m Text
-> (Text -> ParsecT Sources ParserState m [Blocks])
-> ParsecT Sources ParserState m [Blocks]
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ParsecT Sources ParserState m [Blocks]
parseContent)
where
lineContent :: ParsecT Sources ParserState m Text
lineContent = do
Text
content <- ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
Maybe Text
continuation <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (Maybe Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe ParsecT Sources ParserState m Text
listContinuation
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources ParserState m Text)
-> Text -> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
filterSpaces Text
content Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> (Text -> Text) -> Maybe Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" (Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) Maybe Text
continuation
filterSpaces :: Text -> Text
filterSpaces = (Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ')
listContinuation :: ParsecT Sources ParserState m Text
listContinuation = TWParser 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 (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 -> TWParser m a -> TWParser m a
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
>> TWParser m a
marker) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
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
>>
String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
" " ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
lineContent
parseContent :: Text -> ParsecT Sources ParserState m [Blocks]
parseContent = ParsecT Sources ParserState m [Blocks]
-> Text -> ParsecT Sources ParserState m [Blocks]
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' (ParsecT Sources ParserState m [Blocks]
-> Text -> ParsecT Sources ParserState m [Blocks])
-> ParsecT Sources ParserState m [Blocks]
-> Text
-> ParsecT Sources ParserState m [Blocks]
forall a b. (a -> b) -> a -> b
$ 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 (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
$ ParsecT Sources ParserState m Blocks
nestedList 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
parseInline
parseInline :: ParsecT Sources ParserState m Blocks
parseInline = 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 Char
-> 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 => TWParser m Inlines
inline (ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
lastNewline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
newlineBeforeNestedList)
nestedList :: ParsecT Sources ParserState m Blocks
nestedList = Text -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> TWParser m Blocks
list Text
prefix
lastNewline :: ParsecT Sources u m Char
lastNewline = ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Char -> ParsecT Sources u m Char)
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n' ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
newlineBeforeNestedList :: ParsecT Sources ParserState m Char
newlineBeforeNestedList = 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
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Blocks
-> 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 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
lookAhead ParsecT Sources ParserState m Blocks
nestedList
table :: PandocMonad m => TWParser m B.Blocks
table :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
table = 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
Maybe ([(Alignment, ColWidth)], [Blocks])
thead <- ParsecT Sources ParserState m ([(Alignment, ColWidth)], [Blocks])
-> ParsecT
Sources ParserState m (Maybe ([(Alignment, ColWidth)], [Blocks]))
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe ([((Alignment, ColWidth), Blocks)]
-> ([(Alignment, ColWidth)], [Blocks])
forall a b. [(a, b)] -> ([a], [b])
unzip ([((Alignment, ColWidth), Blocks)]
-> ([(Alignment, ColWidth)], [Blocks]))
-> ParsecT Sources ParserState m [((Alignment, ColWidth), Blocks)]
-> ParsecT
Sources ParserState m ([(Alignment, ColWidth)], [Blocks])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ((Alignment, ColWidth), Blocks)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [((Alignment, ColWidth), 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, ColWidth), Blocks)
forall (m :: * -> *).
PandocMonad m =>
TWParser m ((Alignment, ColWidth), Blocks)
tableParseHeader ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline)
[[Blocks]]
rows <- 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 ParsecT Sources ParserState m [Blocks]
forall (m :: * -> *). PandocMonad m => TWParser m [Blocks]
tableParseRow
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
$ Inlines
-> [[Blocks]] -> ([(Alignment, ColWidth)], [Blocks]) -> Blocks
buildTable Inlines
forall a. Monoid a => a
mempty [[Blocks]]
rows (([(Alignment, ColWidth)], [Blocks]) -> Blocks)
-> ([(Alignment, ColWidth)], [Blocks]) -> Blocks
forall a b. (a -> b) -> a -> b
$ ([(Alignment, ColWidth)], [Blocks])
-> Maybe ([(Alignment, ColWidth)], [Blocks])
-> ([(Alignment, ColWidth)], [Blocks])
forall a. a -> Maybe a -> a
fromMaybe ([[Blocks]] -> [(Alignment, ColWidth)]
forall {t :: * -> *} {a}.
Foldable t =>
[t a] -> [(Alignment, ColWidth)]
align [[Blocks]]
rows, [[Blocks]] -> [Blocks]
forall {t :: * -> *} {a} {a}.
(Foldable t, Monoid a) =>
[t a] -> [a]
columns [[Blocks]]
rows) Maybe ([(Alignment, ColWidth)], [Blocks])
thead
where
buildTable :: Inlines
-> [[Blocks]] -> ([(Alignment, ColWidth)], [Blocks]) -> Blocks
buildTable Inlines
caption [[Blocks]]
rows ([(Alignment, ColWidth)]
aligns, [Blocks]
heads)
= Caption
-> [(Alignment, ColWidth)]
-> TableHead
-> [TableBody]
-> TableFoot
-> Blocks
B.table (Blocks -> Caption
B.simpleCaption (Blocks -> Caption) -> Blocks -> Caption
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
B.plain Inlines
caption)
[(Alignment, ColWidth)]
aligns
(Attr -> [Row] -> TableHead
TableHead Attr
nullAttr ([Row] -> TableHead) -> [Row] -> TableHead
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Row]
toHeaderRow [Blocks]
heads)
[Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] ([Row] -> TableBody) -> [Row] -> TableBody
forall a b. (a -> b) -> a -> b
$ ([Blocks] -> Row) -> [[Blocks]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map [Blocks] -> Row
toRow [[Blocks]]
rows]
(Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr [])
align :: [t a] -> [(Alignment, ColWidth)]
align [t a]
rows = Int -> (Alignment, ColWidth) -> [(Alignment, ColWidth)]
forall a. Int -> a -> [a]
replicate ([t a] -> Int
forall {t :: * -> *} {a}. Foldable t => [t a] -> Int
columCount [t a]
rows) (Alignment
AlignDefault, ColWidth
ColWidthDefault)
columns :: [t a] -> [a]
columns [t a]
rows = Int -> a -> [a]
forall a. Int -> a -> [a]
replicate ([t a] -> Int
forall {t :: * -> *} {a}. Foldable t => [t a] -> Int
columCount [t a]
rows) a
forall a. Monoid a => a
mempty
columCount :: [t a] -> Int
columCount [t a]
rows = t a -> Int
forall a. t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (t a -> Int) -> t a -> Int
forall a b. (a -> b) -> a -> b
$ [t a] -> t a
forall a. HasCallStack => [a] -> a
head [t a]
rows
toRow :: [Blocks] -> Row
toRow = Attr -> [Cell] -> Row
Row Attr
nullAttr ([Cell] -> Row) -> ([Blocks] -> [Cell]) -> [Blocks] -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Blocks -> Cell) -> [Blocks] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map Blocks -> Cell
B.simpleCell
toHeaderRow :: [Blocks] -> [Row]
toHeaderRow [Blocks]
l = [[Blocks] -> Row
toRow [Blocks]
l | Bool -> Bool
not ([Blocks] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Blocks]
l)]
tableParseHeader :: PandocMonad m => TWParser m ((Alignment, ColWidth), B.Blocks)
= ParsecT Sources ParserState m ((Alignment, ColWidth), Blocks)
-> ParsecT Sources ParserState m ((Alignment, ColWidth), Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ((Alignment, ColWidth), Blocks)
-> ParsecT Sources ParserState m ((Alignment, ColWidth), Blocks))
-> ParsecT Sources ParserState m ((Alignment, ColWidth), Blocks)
-> ParsecT Sources ParserState m ((Alignment, ColWidth), 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
'|'
Int
leftSpaces <- String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String -> Int)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*'
Blocks
content <- ParsecT Sources ParserState m Char -> TWParser m Blocks
forall (m :: * -> *) a.
PandocMonad m =>
TWParser m a -> TWParser m Blocks
tableColumnContent (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|')
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*'
Int
rightSpaces <- String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String -> Int)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TWParser m Char
tableEndOfRow
((Alignment, ColWidth), Blocks)
-> ParsecT Sources ParserState m ((Alignment, ColWidth), Blocks)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Int -> (Alignment, ColWidth)
forall {a}. (Ord a, Num a) => a -> a -> (Alignment, ColWidth)
tableAlign Int
leftSpaces Int
rightSpaces, Blocks
content)
where
tableAlign :: a -> a -> (Alignment, ColWidth)
tableAlign a
left a
right
| a
left a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
2 Bool -> Bool -> Bool
&& a
left a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
right = (Alignment
AlignCenter, ColWidth
ColWidthDefault)
| a
left a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
right = (Alignment
AlignRight, ColWidth
ColWidthDefault)
| Bool
otherwise = (Alignment
AlignLeft, ColWidth
ColWidthDefault)
tableParseRow :: PandocMonad m => TWParser m [B.Blocks]
tableParseRow :: forall (m :: * -> *). PandocMonad m => TWParser m [Blocks]
tableParseRow = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [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 Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
tableParseColumn ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
tableParseColumn :: PandocMonad m => TWParser m B.Blocks
tableParseColumn :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
tableParseColumn = Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m 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 Char
-> ParsecT Sources ParserState m Blocks
forall (m :: * -> *) a.
PandocMonad m =>
TWParser m a -> TWParser m Blocks
tableColumnContent (ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|')
ParsecT Sources ParserState m 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 ()
skipSpaces 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 Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TWParser m Char
tableEndOfRow
tableEndOfRow :: PandocMonad m => TWParser m Char
tableEndOfRow :: forall (m :: * -> *). PandocMonad m => TWParser m Char
tableEndOfRow = ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ 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 a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n') ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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
'|'
tableColumnContent :: PandocMonad m => TWParser m a -> TWParser m B.Blocks
tableColumnContent :: forall (m :: * -> *) a.
PandocMonad m =>
TWParser m a -> TWParser m Blocks
tableColumnContent TWParser m a
end = 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
-> TWParser m a -> 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
content (TWParser m a -> TWParser m a
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (TWParser m a -> TWParser m a) -> TWParser m a -> TWParser m a
forall a b. (a -> b) -> a -> b
$ TWParser m a -> TWParser m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try TWParser m a
end)
where
content :: ParsecT Sources ParserState m Inlines
content = ParsecT Sources ParserState m Inlines
forall {u}. ParsecT Sources u m Inlines
continuation 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 => TWParser m Inlines
inline
continuation :: ParsecT Sources u m Inlines
continuation = ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines)
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT Sources u m Char
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources u m Char
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
blockQuote :: PandocMonad m => TWParser m B.Blocks
blockQuote :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
blockQuote = Blocks -> Blocks
B.blockQuote (Blocks -> Blocks) -> ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m [Blocks]
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m [a]
parseHtmlContent Text
"blockquote" ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
block
noautolink :: PandocMonad m => TWParser m B.Blocks
noautolink :: forall (m :: * -> *). PandocMonad m => TWParser m Blocks
noautolink = do
(Attr
_, Text
content) <- Text -> TWParser m (Attr, Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m (Attr, Text)
htmlElement Text
"noautolink"
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks = False }
[Blocks]
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
$ Text -> ParsecT Sources ParserState m [Blocks]
parseContent Text
content
ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks = True }
Blocks -> TWParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TWParser m Blocks) -> Blocks -> TWParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
blocks
where
parseContent :: Text -> ParsecT Sources ParserState m [Blocks]
parseContent = ParsecT Sources ParserState m [Blocks]
-> Text -> ParsecT Sources ParserState m [Blocks]
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' (ParsecT Sources ParserState m [Blocks]
-> Text -> ParsecT Sources ParserState m [Blocks])
-> ParsecT Sources ParserState m [Blocks]
-> Text
-> ParsecT Sources ParserState m [Blocks]
forall a b. (a -> b) -> a -> b
$ TWParser m Blocks -> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many TWParser m Blocks
forall (m :: * -> *). PandocMonad m => TWParser m Blocks
block
para :: PandocMonad m => TWParser m B.Blocks
para :: forall (m :: * -> *). PandocMonad m => TWParser 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 => TWParser 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 => TWParser 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
inline :: PandocMonad m => TWParser m B.Inlines
inline :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
inline = [ParsecT Sources ParserState m Inlines]
-> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
whitespace
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
br
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
macro
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
strong
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
strongHtml
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
strongAndEmph
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
emph
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
emphHtml
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
boldCode
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
smart
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
link
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
htmlComment
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
code
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
codeHtml
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
nop
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
autoLink
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
str
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
symbol
] ParsecT Sources ParserState m Inlines
-> String -> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"inline"
whitespace :: PandocMonad m => TWParser m B.Inlines
whitespace :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
whitespace = ParsecT Sources ParserState m Inlines
lb ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
forall {u}. ParsecT Sources u m Inlines
regsp
where lb :: ParsecT Sources ParserState m Inlines
lb = 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 Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
linebreak 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 b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
regsp :: ParsecT Sources u m Inlines
regsp = ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines)
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b. (a -> b) -> a -> 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
spaceChar ParsecT Sources u m ()
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
br :: PandocMonad m => TWParser m B.Inlines
br :: forall (m :: * -> *). PandocMonad m => TWParser 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
$ String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"%BR%" ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.linebreak
linebreak :: PandocMonad m => TWParser m B.Inlines
linebreak :: forall (m :: * -> *). PandocMonad m => TWParser 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 = ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources u m ()
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
innerNewline :: ParsecT Sources ParserState m Inlines
innerNewline = Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
between :: (Monoid c, PandocMonad m, Show b)
=> TWParser m a -> TWParser m b -> (TWParser m b -> TWParser m c)
-> TWParser m c
between :: forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
TWParser m a
-> TWParser m b -> (TWParser m b -> TWParser m c) -> TWParser m c
between TWParser m a
start TWParser m b
end TWParser m b -> TWParser m c
p =
[c] -> c
forall a. Monoid a => [a] -> a
mconcat ([c] -> c) -> ParsecT Sources ParserState m [c] -> TWParser 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 (TWParser m a
start TWParser 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 => TWParser 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
>> TWParser m c -> TWParser 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 (TWParser m b -> TWParser m c
p TWParser m b
end) TWParser m b
end)
enclosed :: (Monoid b, PandocMonad m, Show a)
=> TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
enclosed :: forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
enclosed TWParser m a
sep TWParser m a -> TWParser m b
p = TWParser m a
-> TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
TWParser m a
-> TWParser m b -> (TWParser m b -> TWParser m c) -> TWParser m c
between TWParser m a
sep (TWParser m a -> TWParser m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TWParser m a -> TWParser m a) -> TWParser m a -> TWParser m a
forall a b. (a -> b) -> a -> b
$ TWParser m a
sep TWParser m a -> ParsecT Sources ParserState m () -> TWParser m 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 ()
forall {u}. ParsecT Sources u m ()
endMarker) TWParser m a -> TWParser m b
p
where
endMarker :: ParsecT Sources u m ()
endMarker = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Inlines -> ParsecT Sources u m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources u m Inlines
forall {u}. ParsecT Sources u m Inlines
endSpace ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources u m Char -> ParsecT Sources u m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (String -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
oneOf String
".,!?:)|") ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
endSpace :: ParsecT Sources u m Inlines
endSpace = (ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources u m Char
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline) ParsecT Sources u m Char
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
macro :: PandocMonad m => TWParser m B.Inlines
macro :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
macro = TWParser m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
macroWithParameters TWParser m Inlines -> TWParser m Inlines -> TWParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TWParser m Inlines
withoutParameters
where
withoutParameters :: TWParser m Inlines
withoutParameters = Text -> Inlines
emptySpan (Text -> Inlines)
-> ParsecT Sources ParserState m Text -> TWParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TWParser m Char
-> (TWParser m Char -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
enclosed (Char -> TWParser 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
-> TWParser m Char -> ParsecT Sources ParserState m Text
forall a b. a -> b -> a
const ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => TWParser m Text
macroName)
emptySpan :: Text -> Inlines
emptySpan Text
name = Text -> [Attribute Text] -> Inlines -> Inlines
buildSpan Text
name [] Inlines
forall a. Monoid a => a
mempty
macroWithParameters :: PandocMonad m => TWParser m B.Inlines
macroWithParameters :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
macroWithParameters = 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
name <- TWParser m Text
forall (m :: * -> *). PandocMonad m => TWParser m Text
macroName
(Text
content, [Attribute Text]
kvs) <- TWParser m (Text, [Attribute Text])
forall (m :: * -> *).
PandocMonad m =>
TWParser m (Text, [Attribute Text])
attributes
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
$ Text -> [Attribute Text] -> Inlines -> Inlines
buildSpan Text
name [Attribute Text]
kvs (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
content
buildSpan :: Text -> [(Text, Text)] -> B.Inlines -> B.Inlines
buildSpan :: Text -> [Attribute Text] -> Inlines -> Inlines
buildSpan Text
className [Attribute Text]
kvs = Attr -> Inlines -> Inlines
B.spanWith Attr
attrs
where
attrs :: Attr
attrs = (Text
"", [Text
"twiki-macro", Text
className] [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text]
additionalClasses, [Attribute Text]
kvsWithoutClasses)
additionalClasses :: [Text]
additionalClasses = [Text] -> (Text -> [Text]) -> Maybe Text -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Text -> [Text]
T.words (Maybe Text -> [Text]) -> Maybe Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Attribute Text] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"class" [Attribute Text]
kvs
kvsWithoutClasses :: [Attribute Text]
kvsWithoutClasses = [(Text
k,Text
v) | (Text
k,Text
v) <- [Attribute Text]
kvs, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"class"]
macroName :: PandocMonad m => TWParser m Text
macroName :: forall (m :: * -> *). PandocMonad m => TWParser m Text
macroName = do
Char
first <- ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter
String
rest <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> 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 -> TWParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> TWParser m Text) -> Text -> TWParser m Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Char
firstChar -> String -> String
forall a. a -> [a] -> [a]
:String
rest
attributes :: PandocMonad m => TWParser m (Text, [(Text, Text)])
attributes :: forall (m :: * -> *).
PandocMonad m =>
TWParser m (Text, [Attribute Text])
attributes = (Either Text (Attribute Text)
-> (Text, [Attribute Text]) -> (Text, [Attribute Text]))
-> (Text, [Attribute Text])
-> [Either Text (Attribute Text)]
-> (Text, [Attribute Text])
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((Text -> (Text, [Attribute Text]) -> (Text, [Attribute Text]))
-> (Attribute Text
-> (Text, [Attribute Text]) -> (Text, [Attribute Text]))
-> Either Text (Attribute Text)
-> (Text, [Attribute Text])
-> (Text, [Attribute Text])
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Text -> (Text, [Attribute Text]) -> (Text, [Attribute Text])
forall {a} {b}.
(Eq a, IsString a, Semigroup a) =>
a -> (a, b) -> (a, b)
mkContent Attribute Text
-> (Text, [Attribute Text]) -> (Text, [Attribute Text])
forall {a} {a}. a -> (a, [a]) -> (a, [a])
mkKvs) (Text
"", [])
([Either Text (Attribute Text)] -> (Text, [Attribute Text]))
-> ParsecT Sources ParserState m [Either Text (Attribute Text)]
-> ParsecT Sources ParserState m (Text, [Attribute Text])
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 ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
spnl ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Either Text (Attribute Text)]
-> ParsecT Sources ParserState m [Either Text (Attribute 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 (Either Text (Attribute Text))
-> ParsecT Sources ParserState m [Either Text (Attribute Text)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m (Either Text (Attribute Text))
forall (m :: * -> *).
PandocMonad m =>
TWParser m (Either Text (Attribute Text))
attribute ParsecT Sources ParserState m (Either Text (Attribute Text))
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Either Text (Attribute Text))
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
spnl) ParsecT Sources ParserState m [Either Text (Attribute Text)]
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Either Text (Attribute 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
<* 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
'}')
where
spnl :: ParsecT Sources u m ()
spnl = ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources u m Char
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline)
mkContent :: a -> (a, b) -> (a, b)
mkContent a
c (a
"", b
kvs) = (a
c, b
kvs)
mkContent a
c (a
rest, b
kvs) = (a
c a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
" " a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
rest, b
kvs)
mkKvs :: a -> (a, [a]) -> (a, [a])
mkKvs a
kv (a
cont, [a]
rest) = (a
cont, a
kv a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
rest)
attribute :: PandocMonad m => TWParser m (Either Text (Text, Text))
attribute :: forall (m :: * -> *).
PandocMonad m =>
TWParser m (Either Text (Attribute Text))
attribute = ParsecT Sources ParserState m (Either Text (Attribute Text))
forall {a}.
ParsecT Sources ParserState m (Either a (Attribute Text))
withKey ParsecT Sources ParserState m (Either Text (Attribute Text))
-> ParsecT Sources ParserState m (Either Text (Attribute Text))
-> ParsecT Sources ParserState m (Either Text (Attribute 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 (Either Text (Attribute Text))
forall {b}. ParsecT Sources ParserState m (Either Text b)
withoutKey
where
withKey :: ParsecT Sources ParserState m (Either a (Attribute Text))
withKey = ParsecT Sources ParserState m (Either a (Attribute Text))
-> ParsecT Sources ParserState m (Either a (Attribute Text))
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Either a (Attribute Text))
-> ParsecT Sources ParserState m (Either a (Attribute Text)))
-> ParsecT Sources ParserState m (Either a (Attribute Text))
-> ParsecT Sources ParserState m (Either a (Attribute Text))
forall a b. (a -> b) -> a -> b
$ do
Text
key <- TWParser m Text
forall (m :: * -> *). PandocMonad m => TWParser m Text
macroName
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
'='
(Attribute Text -> Either a (Attribute Text))
-> Text -> Text -> Either a (Attribute Text)
forall a b c. ((a, b) -> c) -> a -> b -> c
curry Attribute Text -> Either a (Attribute Text)
forall a b. b -> Either a b
Right Text
key (Text -> Either a (Attribute Text))
-> TWParser m Text
-> ParsecT Sources ParserState m (Either a (Attribute Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> TWParser m Text
parseValue Bool
False
withoutKey :: ParsecT Sources ParserState m (Either Text b)
withoutKey = ParsecT Sources ParserState m (Either Text b)
-> ParsecT Sources ParserState m (Either Text b)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Either Text b)
-> ParsecT Sources ParserState m (Either Text b))
-> ParsecT Sources ParserState m (Either Text b)
-> ParsecT Sources ParserState m (Either Text b)
forall a b. (a -> b) -> a -> b
$ Text -> Either Text b
forall a b. a -> Either a b
Left (Text -> Either Text b)
-> TWParser m Text -> ParsecT Sources ParserState m (Either Text b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> TWParser m Text
parseValue Bool
True
parseValue :: Bool -> TWParser m Text
parseValue Bool
allowSpaces = Text -> Text
fromEntities (Text -> Text) -> TWParser m Text -> TWParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TWParser m Text
withQuotes TWParser m Text -> TWParser m Text -> TWParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> TWParser m Text
forall {s} {m :: * -> *} {st}.
(Stream s m Char, UpdateSourcePos s Char) =>
Bool -> ParsecT s st m Text
withoutQuotes Bool
allowSpaces)
withQuotes :: TWParser m Text
withQuotes = ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> (ParsecT Sources ParserState m Char -> TWParser m Text)
-> TWParser m Text
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
TWParser m a
-> TWParser m b -> (TWParser m b -> TWParser m c) -> TWParser m c
between (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"') (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"') (\ParsecT Sources ParserState m Char
_ -> Int -> ParsecT Sources ParserState m Char -> TWParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 (ParsecT Sources ParserState m Char -> TWParser m Text)
-> ParsecT Sources ParserState m Char -> TWParser m Text
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf [Char
'"'])
withoutQuotes :: Bool -> ParsecT s st m Text
withoutQuotes Bool
allowSpaces
| Bool
allowSpaces = ParsecT s st m Char -> ParsecT s st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (ParsecT s st m Char -> ParsecT s st m Text)
-> ParsecT s st m Char -> ParsecT s st m Text
forall a b. (a -> b) -> a -> b
$ String -> ParsecT s st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"}"
| Bool
otherwise = ParsecT s st m Char -> ParsecT s st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char (ParsecT s st m Char -> ParsecT s st m Text)
-> ParsecT s st m Char -> ParsecT s st m Text
forall a b. (a -> b) -> a -> b
$ String -> ParsecT s st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
" }"
nestedInlines :: (Show a, PandocMonad m)
=> TWParser m a -> TWParser m B.Inlines
nestedInlines :: forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TWParser m a -> TWParser m Inlines
nestedInlines TWParser 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 => TWParser 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
<* TWParser 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 TWParser 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 => TWParser 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 => TWParser m Inlines
inline
strong :: PandocMonad m => TWParser m B.Inlines
strong :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
strong = 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
<$> TWParser m Char
-> (TWParser m Char -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
enclosed (Char -> TWParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*') TWParser m Char -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TWParser m a -> TWParser m Inlines
nestedInlines
strongHtml :: PandocMonad m => TWParser m B.Inlines
strongHtml :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
strongHtml = Inlines -> Inlines
B.strong (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
<$> (Text
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Inlines]
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m [a]
parseHtmlContent Text
"strong" ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
inline 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
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Inlines]
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m [a]
parseHtmlContent Text
"b" ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
inline)
strongAndEmph :: PandocMonad m => TWParser m B.Inlines
strongAndEmph :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
strongAndEmph = 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) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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
<$> TWParser m String
-> (TWParser m String -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
enclosed (String -> TWParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"__") TWParser m String -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TWParser m a -> TWParser m Inlines
nestedInlines
emph :: PandocMonad m => TWParser m B.Inlines
emph :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
emph = 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
<$> TWParser m Char
-> (TWParser m Char -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
enclosed (Char -> TWParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'_')
(\TWParser m Char
p -> TWParser m Char -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Char -> TWParser 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 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
>> TWParser m Char -> ParsecT Sources ParserState m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TWParser m a -> TWParser m Inlines
nestedInlines TWParser m Char
p)
emphHtml :: PandocMonad m => TWParser m B.Inlines
emphHtml :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
emphHtml = Inlines -> Inlines
B.emph (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
<$> (Text
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Inlines]
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m [a]
parseHtmlContent Text
"em" ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
inline 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
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Inlines]
forall (m :: * -> *) a.
PandocMonad m =>
Text -> TWParser m a -> TWParser m [a]
parseHtmlContent Text
"i" ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
inline)
nestedString :: (Show a, PandocMonad m)
=> TWParser m a -> TWParser m Text
nestedString :: forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TWParser m a -> TWParser m Text
nestedString TWParser 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
<|> Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 ParsecT Sources ParserState m Char
forall 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
<* TWParser 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 TWParser m a
end
boldCode :: PandocMonad m => TWParser m B.Inlines
boldCode :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
boldCode = 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) -> (Text -> Inlines) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.code (Text -> Inlines) -> (Text -> Text) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TWParser m String
-> (TWParser m String -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
enclosed (String -> TWParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"==") TWParser m String -> ParsecT Sources ParserState m Text
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TWParser m a -> TWParser m Text
nestedString
htmlComment :: PandocMonad m => TWParser m B.Inlines
= (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isCommentTag ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
code :: PandocMonad m => TWParser m B.Inlines
code :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
code = 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) -> (Text -> Text) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TWParser m Char
-> (TWParser m Char -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
enclosed (Char -> TWParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'=') TWParser m Char -> ParsecT Sources ParserState m Text
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TWParser m a -> TWParser m Text
nestedString
codeHtml :: PandocMonad m => TWParser m B.Inlines
codeHtml :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
codeHtml = do
(Attr
attrs, Text
content) <- Text -> TWParser m Char -> TWParser m (Attr, Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> TWParser m Char -> TWParser m (Attr, Text)
parseCharHtmlContentWithAttrs Text
"code" TWParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
Inlines -> TWParser m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TWParser m Inlines) -> Inlines -> TWParser m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Inlines
B.codeWith Attr
attrs (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text
fromEntities Text
content
autoLink :: PandocMonad m => TWParser m B.Inlines
autoLink :: forall (m :: * -> *). PandocMonad m => TWParser 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 (Attribute Text)
parseLink
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
$ Attribute Text -> Inlines
makeLink (Text
text, Text
url)
where
parseLink :: ParsecT Sources ParserState m (Attribute Text)
parseLink = 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 => TWParser m Inlines
nop ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Attribute Text)
-> ParsecT Sources ParserState m (Attribute Text)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ParsecT Sources ParserState m (Attribute Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (Attribute Text)
uri ParsecT Sources ParserState m (Attribute Text)
-> ParsecT Sources ParserState m (Attribute Text)
-> ParsecT Sources ParserState m (Attribute 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 (Attribute Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (Attribute Text)
emailAddress)
makeLink :: Attribute 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
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
str :: PandocMonad m => TWParser m B.Inlines
str :: forall (m :: * -> *). PandocMonad m => TWParser 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)
nop :: PandocMonad m => TWParser m B.Inlines
nop :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
nop = 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 Char
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
exclamation ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT Sources ParserState m Text
forall {st}. ParsecT Sources st m Text
nopTag) 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 {st}. ParsecT Sources st m Inlines
followContent
where
exclamation :: ParsecT Sources u m Char
exclamation = Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'!'
nopTag :: ParsecT Sources st m Text
nopTag = Text -> ParsecT Sources st m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
stringAnyCase Text
"<nop>"
followContent :: ParsecT Sources st m Inlines
followContent = Text -> Inlines
B.str (Text -> Inlines) -> (Text -> Text) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities (Text -> Inlines)
-> ParsecT Sources st m Text -> ParsecT Sources st m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources st m Char -> ParsecT Sources st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources st m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar
symbol :: PandocMonad m => TWParser m B.Inlines
symbol :: forall (m :: * -> *). PandocMonad m => TWParser 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
<$> Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar
smart :: PandocMonad m => TWParser m B.Inlines
smart :: forall (m :: * -> *). PandocMonad m => TWParser m Inlines
smart = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall st (m :: * -> *) s.
(HasReaderOptions st, HasLastStrPosition st, HasQuoteContext st m,
Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines -> ParsecT s st m Inlines
smartPunctuation ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
inline
link :: PandocMonad m => TWParser m B.Inlines
link :: forall (m :: * -> *). PandocMonad m => TWParser 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 = False }
(Text
url, Text
title, Inlines
content) <- TWParser m (Text, Text, Inlines)
forall (m :: * -> *).
PandocMonad m =>
TWParser m (Text, Text, 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 = 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 -> ParsecT Sources ParserState m Inlines)
-> Inlines -> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link Text
url Text
title Inlines
content
linkText :: PandocMonad m => TWParser m (Text, Text, B.Inlines)
linkText :: forall (m :: * -> *).
PandocMonad m =>
TWParser m (Text, Text, Inlines)
linkText = do
String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"[["
Text
url <- String -> Text
T.pack (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
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 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
']')
Inlines
content <- Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Text -> Inlines
B.str Text
url) ([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]
linkContent)
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, Inlines) -> TWParser m (Text, Text, Inlines)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
url, Text
"", Inlines
content)
where
linkContent :: ParsecT Sources ParserState m [Inlines]
linkContent = 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 String
-> ParsecT Sources ParserState m String
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
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 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 String
-> (String -> ParsecT Sources ParserState m [Inlines])
-> ParsecT Sources ParserState m [Inlines]
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ParsecT Sources ParserState m [Inlines]
parseLinkContent (Text -> ParsecT Sources ParserState m [Inlines])
-> (String -> Text)
-> String
-> ParsecT Sources ParserState m [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
parseLinkContent :: Text -> ParsecT Sources ParserState m [Inlines]
parseLinkContent = ParsecT Sources ParserState m [Inlines]
-> Text -> ParsecT Sources ParserState m [Inlines]
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' (ParsecT Sources ParserState m [Inlines]
-> Text -> ParsecT Sources ParserState m [Inlines])
-> ParsecT Sources ParserState m [Inlines]
-> Text
-> ParsecT Sources ParserState m [Inlines]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TWParser m Inlines
inline