{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
module Text.Pandoc.Readers.Textile ( readTextile) where
import Control.Monad (guard, liftM)
import Control.Monad.Except (throwError)
import Data.Char (digitToInt, isUpper)
import Data.List (intersperse, transpose, foldl')
import Data.List.NonEmpty (NonEmpty(..), nonEmpty)
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
import Text.HTML.TagSoup (Tag (..), fromAttrib)
import Text.HTML.TagSoup.Match
import Text.Pandoc.Builder (Blocks, Inlines, trimInlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.CSS
import Text.Pandoc.Definition
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Parsing
import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isInlineTag)
import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline)
import Text.Pandoc.Shared (trim, tshow)
import Text.Read (readMaybe)
readTextile :: (PandocMonad m, ToSources a)
=> ReaderOptions
-> a
-> m Pandoc
readTextile :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readTextile 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
parsed <- ParsecT Sources ParserState m Pandoc
-> ParserState -> Sources -> m (Either PandocError Pandoc)
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParsecT Sources ParserState m Pandoc
forall (m :: * -> *). PandocMonad m => TextileParser m Pandoc
parseTextile ParserState
forall a. Default a => a
def{ stateOptions = opts } Sources
sources
case Either PandocError Pandoc
parsed of
Right Pandoc
result -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
result
Left PandocError
e -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
type TextileParser = ParsecT Sources ParserState
parseTextile :: PandocMonad m => TextileParser m Pandoc
parseTextile :: forall (m :: * -> *). PandocMonad m => TextileParser m Pandoc
parseTextile = do
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]
many ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
SourcePos
startPos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
let firstPassParser :: ParsecT Sources ParserState m (SourcePos, Text)
firstPassParser = do
SourcePos
pos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
Text
t <- TextileParser m Text
forall (m :: * -> *). PandocMonad m => TextileParser m Text
noteBlock TextileParser m Text
-> TextileParser m Text -> TextileParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TextileParser m Text
forall (m :: * -> *). PandocMonad m => TextileParser m Text
referenceKey TextileParser m Text
-> TextileParser m Text -> TextileParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TextileParser m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
lineClump
(SourcePos, Text)
-> ParsecT Sources ParserState m (SourcePos, Text)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (SourcePos
pos, Text
t)
ParsecT Sources ParserState m (SourcePos, Text)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [(SourcePos, Text)]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m (SourcePos, Text)
firstPassParser ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources ParserState m [(SourcePos, Text)]
-> ([(SourcePos, Text)] -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> (a -> ParsecT Sources ParserState m b)
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Sources -> ParsecT Sources ParserState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput (Sources -> ParsecT Sources ParserState m ())
-> ([(SourcePos, Text)] -> Sources)
-> [(SourcePos, Text)]
-> ParsecT Sources ParserState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(SourcePos, Text)] -> Sources
Sources
SourcePos -> ParsecT Sources ParserState m ()
forall (m :: * -> *) s u. Monad m => SourcePos -> ParsecT s u m ()
setPosition SourcePos
startPos
ParserState
st' <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let reversedNotes :: NoteTable
reversedNotes = ParserState -> NoteTable
stateNotes ParserState
st'
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
s -> ParserState
s { stateNotes = reverse reversedNotes }
Meta -> [Block] -> Pandoc
Pandoc Meta
nullMeta ([Block] -> Pandoc)
-> (Many Block -> [Block]) -> Many Block -> Pandoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Many Block -> [Block]
forall a. Many a -> [a]
B.toList (Many Block -> Pandoc)
-> ParsecT Sources ParserState m (Many Block)
-> TextileParser m Pandoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
parseBlocks
noteMarker :: PandocMonad m => TextileParser m Text
noteMarker :: forall (m :: * -> *). PandocMonad m => TextileParser m Text
noteMarker = do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
[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]
string [Char]
"fn"
[Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char] -> TextileParser 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 [Char]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit ([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]
string [Char]
"." ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char] -> ParsecT Sources ParserState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"^."))
noteBlock :: PandocMonad m => TextileParser m Text
noteBlock :: forall (m :: * -> *). PandocMonad m => TextileParser m Text
noteBlock = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
SourcePos
startPos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
Text
ref <- ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => TextileParser m Text
noteMarker
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
Text
contents <- [Text] -> Text
T.unlines ([Text] -> Text)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
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 Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine (ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => TextileParser m Text
noteBlock)
SourcePos
endPos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
let newnote :: (Text, Text)
newnote = (Text
ref, Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n")
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let oldnotes :: NoteTable
oldnotes = ParserState -> NoteTable
stateNotes ParserState
st
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
s -> ParserState
s { stateNotes = newnote : oldnotes }
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
$ Int -> Text -> Text
T.replicate (SourcePos -> Int
sourceLine SourcePos
endPos Int -> Int -> Int
forall a. Num a => a -> a -> a
- SourcePos -> Int
sourceLine SourcePos
startPos) Text
"\n"
referenceKey :: PandocMonad m => TextileParser m Text
referenceKey :: forall (m :: * -> *). PandocMonad m => TextileParser m Text
referenceKey = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
SourcePos
pos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
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
refName <- [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
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 s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']')
Text
refDestination <- [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
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 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let oldKeys :: KeyTable
oldKeys = ParserState -> KeyTable
stateKeys ParserState
st
let key :: Key
key = Text -> Key
toKey Text
refName
let target :: (Text, Text)
target = (Text
refDestination, Text
"")
case Key -> KeyTable -> Maybe ((Text, Text), Attr)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Key
key KeyTable
oldKeys of
Just ((Text, Text)
t, Attr
_) | Bool -> Bool
not ((Text, Text)
t (Text, Text) -> (Text, Text) -> Bool
forall a. Eq a => a -> a -> Bool
== (Text, Text)
target) ->
LogMessage -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLogMessages st) =>
LogMessage -> ParsecT s st m ()
logMessage (LogMessage -> ParsecT Sources ParserState m ())
-> LogMessage -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
DuplicateLinkReference Text
refName SourcePos
pos
Maybe ((Text, Text), Attr)
_ -> () -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
s -> ParserState
s {stateKeys = M.insert key (target, nullAttr) oldKeys }
Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\n"
parseBlocks :: PandocMonad m => TextileParser m Blocks
parseBlocks :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
parseBlocks = [Many Block] -> Many Block
forall a. Monoid a => [a] -> a
mconcat ([Many Block] -> Many Block)
-> ParsecT Sources ParserState m [Many Block]
-> ParsecT Sources ParserState m (Many Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Many Block]
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 (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
block ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
blockParsers :: PandocMonad m => [TextileParser m Blocks]
blockParsers :: forall (m :: * -> *).
PandocMonad m =>
[TextileParser m (Many Block)]
blockParsers = [ TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
codeBlock
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
header
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
blockQuote
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
hrule
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
commentBlock
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
anyList
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
rawHtmlBlock
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
rawLaTeXBlock'
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
table
, Text
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Text
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
explicitBlock Text
"p" (TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
para TextileParser m (Many Block)
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Many Block -> TextileParser m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> Many Block
B.para Inlines
forall a. Monoid a => a
mempty))
, TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
para
, Many Block
forall a. Monoid a => a
mempty Many Block
-> ParsecT Sources ParserState m Text
-> TextileParser m (Many Block)
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
]
block :: PandocMonad m => TextileParser m Blocks
block :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
block = do
Many Block
res <- [TextileParser m (Many Block)] -> TextileParser m (Many Block)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [TextileParser m (Many Block)]
forall (m :: * -> *).
PandocMonad m =>
[TextileParser m (Many Block)]
blockParsers TextileParser m (Many Block)
-> [Char] -> TextileParser m (Many Block)
forall s u (m :: * -> *) a.
ParsecT s u m a -> [Char] -> ParsecT s u m a
<?> [Char]
"block"
Text -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => Text -> m ()
trace (Int -> Text -> Text
T.take Int
60 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Block] -> Text
forall a. Show a => a -> Text
tshow ([Block] -> Text) -> [Block] -> Text
forall a b. (a -> b) -> a -> b
$ Many Block -> [Block]
forall a. Many a -> [a]
B.toList Many Block
res)
Many Block -> TextileParser m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Many Block
res
commentBlock :: PandocMonad m => TextileParser m Blocks
= ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
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]
string [Char]
"###."
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Many Block -> ParsecT Sources ParserState m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Many Block
forall a. Monoid a => a
mempty
codeBlock :: PandocMonad m => TextileParser m Blocks
codeBlock :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
codeBlock = TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
codeBlockTextile TextileParser m (Many Block)
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
codeBlockHtml
codeBlockTextile :: PandocMonad m => TextileParser m Blocks
codeBlockTextile :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
codeBlockTextile = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
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]
string [Char]
"bc." 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]
string [Char]
"pre."
Bool
extended <- Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (Bool
True Bool
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'.')
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' '
let starts :: [Text]
starts = [Text
"p", Text
"table", Text
"bq", Text
"bc", Text
"pre", Text
"h1", Text
"h2", Text
"h3",
Text
"h4", Text
"h5", Text
"h6", Text
"pre", Text
"###", Text
"notextile"]
let ender :: ParsecT Sources ParserState m ()
ender = () ()
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [ParsecT Sources ParserState m Attr]
-> ParsecT Sources ParserState m Attr
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 Attr)
-> [Text] -> [ParsecT Sources ParserState m Attr]
forall a b. (a -> b) -> [a] -> [b]
map Text -> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => Text -> TextileParser m Attr
explicitBlockStart [Text]
starts)
[Text]
contents <- if Bool
extended
then do
Text
f <- ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
[Text]
rest <- ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m ()
-> 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 ()
ender ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine)
[Text] -> ParsecT Sources ParserState m [Text]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
fText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
rest)
else ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m [Text]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Many Block -> ParsecT Sources ParserState m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Block -> ParsecT Sources ParserState m (Many Block))
-> Many Block -> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ Text -> Many Block
B.codeBlock (Text -> Text
trimTrailingNewlines ([Text] -> Text
T.unlines [Text]
contents))
trimTrailingNewlines :: Text -> Text
trimTrailingNewlines :: Text -> Text
trimTrailingNewlines = (Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'\n')
codeBlockHtml :: PandocMonad m => TextileParser m Blocks
codeBlockHtml :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
codeBlockHtml = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ do
(t :: Tag Text
t@(TagOpen Text
_ NoteTable
attrs),Text
_) <- (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag ((Text -> Bool) -> (NoteTable -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"pre") (Bool -> NoteTable -> Bool
forall a b. a -> b -> a
const Bool
True))
Text
result' <- [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag ((Text -> Bool) -> Tag Text -> Bool
forall str. (str -> Bool) -> Tag str -> Bool
tagClose (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"pre")))
let result'' :: Text
result'' = case Text -> Maybe (Char, Text)
T.uncons Text
result' of
Just (Char
'\n', Text
xs) -> Text
xs
Maybe (Char, Text)
_ -> Text
result'
let result''' :: Text
result''' = case Text -> Maybe (Text, Char)
T.unsnoc Text
result'' of
Just (Text
xs, Char
'\n') -> Text
xs
Maybe (Text, Char)
_ -> Text
result''
let classes :: [Text]
classes = Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"class" Tag Text
t
let ident :: Text
ident = Text -> Tag Text -> Text
forall str.
(Show str, Eq str, StringLike str) =>
str -> Tag str -> str
fromAttrib Text
"id" Tag Text
t
let kvs :: NoteTable
kvs = [(Text
k,Text
v) | (Text
k,Text
v) <- NoteTable
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"]
Many Block -> ParsecT Sources ParserState m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Block -> ParsecT Sources ParserState m (Many Block))
-> Many Block -> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Many Block
B.codeBlockWith (Text
ident,[Text]
classes,NoteTable
kvs) Text
result'''
header :: PandocMonad m => TextileParser m Blocks
= ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
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
'h'
Int
level <- Char -> Int
digitToInt (Char -> Int)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Int
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
oneOf [Char]
"123456"
Attr
attr <- TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
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
'.'
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
lookAhead ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace
Inlines
name <- Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT 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 [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
inline
Attr
attr' <- Attr -> Inlines -> TextileParser m Attr
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
HasIdentifierList st) =>
Attr -> Inlines -> ParsecT s st m Attr
registerHeader Attr
attr Inlines
name
Many Block -> ParsecT Sources ParserState m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Block -> ParsecT Sources ParserState m (Many Block))
-> Many Block -> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Inlines -> Many Block
B.headerWith Attr
attr' Int
level Inlines
name
blockQuote :: PandocMonad m => TextileParser m Blocks
blockQuote :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
blockQuote = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
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]
string [Char]
"bq" ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
attributes ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'.' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m 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 => TextileParser m Inlines
whitespace
Many Block -> Many Block
B.blockQuote (Many Block -> Many Block)
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
para
hrule :: PandocMonad m => TextileParser m Blocks
hrule :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
hrule = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Char
start <- [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
oneOf [Char]
"-*"
Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
2 (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
start)
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m 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
start)
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 Text
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Many Block -> ParsecT Sources ParserState m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Many Block
B.horizontalRule
anyList :: PandocMonad m => TextileParser m Blocks
anyList :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
anyList = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ Int -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
anyListAtDepth Int
1 ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m (Many Block)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
anyListAtDepth :: PandocMonad m => Int -> TextileParser m Blocks
anyListAtDepth :: forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
anyListAtDepth Int
depth = [ParsecT Sources ParserState m (Many Block)]
-> ParsecT Sources ParserState m (Many Block)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Int -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
bulletListAtDepth Int
depth,
Int -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
orderedListAtDepth Int
depth,
ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
definitionList ]
bulletListAtDepth :: PandocMonad m => Int -> TextileParser m Blocks
bulletListAtDepth :: forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
bulletListAtDepth Int
depth = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ [Many Block] -> Many Block
B.bulletList ([Many Block] -> Many Block)
-> ParsecT Sources ParserState m [Many Block]
-> ParsecT Sources ParserState m (Many Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m [Many Block]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Int -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
bulletListItemAtDepth Int
depth)
bulletListItemAtDepth :: PandocMonad m => Int -> TextileParser m Blocks
bulletListItemAtDepth :: forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
bulletListItemAtDepth Int
depth = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ do
Int -> TextileParser m ()
forall (m :: * -> *). PandocMonad m => Int -> TextileParser m ()
bulletListStartAtDepth Int
depth
Int -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
genericListItemContentsAtDepth Int
depth
orderedListAtDepth :: PandocMonad m => Int -> TextileParser m Blocks
orderedListAtDepth :: forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
orderedListAtDepth Int
depth = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ do
(Int
startNum, Many Block
firstItem) <- Int -> TextileParser m (Int, Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Int, Many Block)
firstOrderedListItemAtDepth Int
depth
[Many Block]
moreItems <- ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m [Many Block]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Int -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
orderedListItemAtDepth Int
depth)
let listItems :: [Many Block]
listItems = Many Block
firstItem Many Block -> [Many Block] -> [Many Block]
forall a. a -> [a] -> [a]
: [Many Block]
moreItems
Many Block -> ParsecT Sources ParserState m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Block -> ParsecT Sources ParserState m (Many Block))
-> Many Block -> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ ListAttributes -> [Many Block] -> Many Block
B.orderedListWith (Int
startNum, ListNumberStyle
DefaultStyle, ListNumberDelim
DefaultDelim) [Many Block]
listItems
firstOrderedListItemAtDepth :: PandocMonad m => Int
-> TextileParser m (Int, Blocks)
firstOrderedListItemAtDepth :: forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Int, Many Block)
firstOrderedListItemAtDepth Int
depth = ParsecT Sources ParserState m (Int, Many Block)
-> ParsecT Sources ParserState m (Int, Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Int, Many Block)
-> ParsecT Sources ParserState m (Int, Many Block))
-> ParsecT Sources ParserState m (Int, Many Block)
-> ParsecT Sources ParserState m (Int, Many Block)
forall a b. (a -> b) -> a -> b
$ do
Int
startNum <- Int -> TextileParser m Int
forall (m :: * -> *). PandocMonad m => Int -> TextileParser m Int
orderedListStartAtDepth Int
depth
Many Block
contents <- Int -> TextileParser m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
genericListItemContentsAtDepth Int
depth
(Int, Many Block)
-> ParsecT Sources ParserState m (Int, Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
startNum, Many Block
contents)
orderedListItemAtDepth :: PandocMonad m => Int -> TextileParser m Blocks
orderedListItemAtDepth :: forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
orderedListItemAtDepth Int
depth = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ do
Int -> TextileParser m Int
forall (m :: * -> *). PandocMonad m => Int -> TextileParser m Int
orderedListStartAtDepth Int
depth
Int -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
genericListItemContentsAtDepth Int
depth
orderedListStartAtDepth :: PandocMonad m => Int -> TextileParser m Int
orderedListStartAtDepth :: forall (m :: * -> *). PandocMonad m => Int -> TextileParser m Int
orderedListStartAtDepth Int
depth = Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
depth (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 Int
-> ParsecT Sources ParserState m Int
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Int
forall (m :: * -> *). PandocMonad m => TextileParser m Int
orderedListStartAttr ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Int
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
attributes TextileParser m Attr
-> 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 => TextileParser m Inlines
whitespace)
bulletListStartAtDepth :: PandocMonad m => Int -> TextileParser m ()
bulletListStartAtDepth :: forall (m :: * -> *). PandocMonad m => Int -> TextileParser m ()
bulletListStartAtDepth Int
depth = () ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
depth (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 Attr
-> ParsecT Sources ParserState m Attr
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
attributes ParsecT Sources ParserState m Attr
-> 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 => TextileParser m Inlines
whitespace)
genericListItemContentsAtDepth :: PandocMonad m => Int
-> TextileParser m Blocks
genericListItemContentsAtDepth :: forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
genericListItemContentsAtDepth Int
depth = do
Many Block
contents <- [Many Block] -> Many Block
forall a. Monoid a => [a] -> a
mconcat ([Many Block] -> Many Block)
-> ParsecT Sources ParserState m [Many Block]
-> TextileParser m (Many Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TextileParser m (Many Block)
-> ParsecT Sources ParserState m [Many Block]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ((Inlines -> Many Block
B.plain (Inlines -> Many Block)
-> ([Inlines] -> Inlines) -> [Inlines] -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Many Block)
-> ParsecT Sources ParserState m [Inlines]
-> TextileParser m (Many Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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 => TextileParser m Inlines
inline) TextileParser m (Many Block)
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
TextileParser m (Many Block) -> TextileParser m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
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
>> TextileParser m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
codeBlockHtml))
ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
Many Block
sublist <- Many Block
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Many Block
forall a. Monoid a => a
mempty (Int -> TextileParser m (Many Block)
forall (m :: * -> *).
PandocMonad m =>
Int -> TextileParser m (Many Block)
anyListAtDepth (Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
Many Block -> TextileParser m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Block -> TextileParser m (Many Block))
-> Many Block -> TextileParser m (Many Block)
forall a b. (a -> b) -> a -> b
$ Many Block
contents Many Block -> Many Block -> Many Block
forall a. Semigroup a => a -> a -> a
<> Many Block
sublist
definitionList :: PandocMonad m => TextileParser m Blocks
definitionList :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
definitionList = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ [(Inlines, [Many Block])] -> Many Block
B.definitionList ([(Inlines, [Many Block])] -> Many Block)
-> ParsecT Sources ParserState m [(Inlines, [Many Block])]
-> ParsecT Sources ParserState m (Many Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Inlines, [Many Block])
-> ParsecT Sources ParserState m [(Inlines, [Many Block])]
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, [Many Block])
forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Inlines, [Many Block])
definitionListItem
listStart :: PandocMonad m => TextileParser m ()
listStart :: forall (m :: * -> *). PandocMonad m => TextileParser m ()
listStart = Char -> TextileParser m ()
forall (m :: * -> *). PandocMonad m => Char -> TextileParser m ()
genericListStart Char
'*'
TextileParser m () -> TextileParser m () -> TextileParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () () -> TextileParser m () -> TextileParser m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ TextileParser m ()
forall (m :: * -> *). PandocMonad m => TextileParser m ()
orderedListStart
TextileParser m () -> TextileParser m () -> TextileParser 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 Inlines -> TextileParser m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
definitionListStart
genericListStart :: PandocMonad m => Char -> TextileParser m ()
genericListStart :: forall (m :: * -> *). PandocMonad m => Char -> TextileParser m ()
genericListStart Char
c = () ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m 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 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]
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
c) ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace)
orderedListStart :: PandocMonad m => TextileParser m ()
orderedListStart :: forall (m :: * -> *). PandocMonad m => TextileParser m ()
orderedListStart = () ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m 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 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]
many1 (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'#') ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT Sources ParserState m Int
-> ParsecT Sources ParserState m Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources ParserState m Int
forall (m :: * -> *). PandocMonad m => TextileParser m Int
orderedListStartAttr ParsecT Sources ParserState m Int
-> 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 => TextileParser m Inlines
whitespace)
basicDLStart :: PandocMonad m => TextileParser m ()
basicDLStart :: forall (m :: * -> *). PandocMonad m => TextileParser m ()
basicDLStart = 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
'-'
TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace
ParsecT Sources ParserState m Char -> TextileParser 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
definitionListStart :: PandocMonad m => TextileParser m Inlines
definitionListStart :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
definitionListStart = 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
TextileParser m ()
forall (m :: * -> *). PandocMonad m => TextileParser m ()
basicDLStart
Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT 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
-> TextileParser 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 => TextileParser m Inlines
inline
( TextileParser m () -> TextileParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> TextileParser m () -> TextileParser 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
*> TextileParser m () -> TextileParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead TextileParser m ()
forall (m :: * -> *). PandocMonad m => TextileParser m ()
basicDLStart)
TextileParser m () -> TextileParser m () -> TextileParser m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TextileParser m () -> TextileParser m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TextileParser m () -> TextileParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (() () -> ParsecT Sources ParserState m [Char] -> TextileParser m ()
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [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]
string [Char]
":="))
)
definitionListItem :: PandocMonad m => TextileParser m (Inlines, [Blocks])
definitionListItem :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Inlines, [Many Block])
definitionListItem = ParsecT Sources ParserState m (Inlines, [Many Block])
-> ParsecT Sources ParserState m (Inlines, [Many Block])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Inlines, [Many Block])
-> ParsecT Sources ParserState m (Inlines, [Many Block]))
-> ParsecT Sources ParserState m (Inlines, [Many Block])
-> ParsecT Sources ParserState m (Inlines, [Many Block])
forall a b. (a -> b) -> a -> b
$ do
Inlines
term <- [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse Inlines
B.linebreak ([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 [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 => TextileParser m Inlines
definitionListStart
[Many Block]
def' <- [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]
string [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 Inlines
-> 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 Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Many Block]
-> ParsecT Sources ParserState m [Many Block]
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 [Many Block]
forall (m :: * -> *). PandocMonad m => TextileParser m [Many Block]
multilineDef ParsecT Sources ParserState m [Many Block]
-> ParsecT Sources ParserState m [Many Block]
-> ParsecT Sources ParserState m [Many Block]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m [Many Block]
forall (m :: * -> *). PandocMonad m => TextileParser m [Many Block]
inlineDef)
(Inlines, [Many Block])
-> ParsecT Sources ParserState m (Inlines, [Many Block])
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
term, [Many Block]
def')
where inlineDef :: PandocMonad m => TextileParser m [Blocks]
inlineDef :: forall (m :: * -> *). PandocMonad m => TextileParser m [Many Block]
inlineDef = (Inlines -> [Many Block])
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Many Block]
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (\Inlines
d -> [Inlines -> Many Block
B.plain Inlines
d])
(ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Many Block])
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Many Block]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Inlines
-> 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 Inlines
forall (m :: * -> *). PandocMonad m => TextileParser 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
>> (Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT 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 [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
inline) ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
multilineDef :: PandocMonad m => TextileParser m [Blocks]
multilineDef :: forall (m :: * -> *). PandocMonad m => TextileParser m [Many Block]
multilineDef = ParsecT Sources ParserState m [Many Block]
-> ParsecT Sources ParserState m [Many Block]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Many Block]
-> ParsecT Sources ParserState m [Many Block])
-> ParsecT Sources ParserState m [Many Block]
-> ParsecT Sources ParserState m [Many Block]
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Inlines
-> 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 Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
Text
s <- [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
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 (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char] -> ParsecT Sources ParserState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [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
>> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline))
Many Block
ds <- ParsecT Sources ParserState m (Many Block)
-> Text -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
parseBlocks (Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n\n")
[Many Block] -> ParsecT Sources ParserState m [Many Block]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return [Many Block
ds]
rawHtmlBlock :: PandocMonad m => TextileParser m Blocks
rawHtmlBlock :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
rawHtmlBlock = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
(Tag Text
_,Text
b) <- (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isBlockTag
ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
Many Block -> ParsecT Sources ParserState m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Block -> ParsecT Sources ParserState m (Many Block))
-> Many Block -> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Many Block
B.rawBlock Text
"html" Text
b
rawLaTeXBlock' :: PandocMonad m => TextileParser m Blocks
rawLaTeXBlock' :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
rawLaTeXBlock' = do
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_tex
Text -> Text -> Many Block
B.rawBlock Text
"latex" (Text -> Many Block)
-> ParsecT Sources ParserState m Text
-> TextileParser m (Many Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m Text
forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
ParsecT Sources s m Text
rawLaTeXBlock ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces)
para :: PandocMonad m => TextileParser m Blocks
para :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
para = Inlines -> Many Block
B.para (Inlines -> Many Block)
-> ([Inlines] -> Inlines) -> [Inlines] -> Many Block
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Many Block)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m (Many Block)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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 => TextileParser m Inlines
inline
toAlignment :: Char -> Alignment
toAlignment :: Char -> Alignment
toAlignment Char
'<' = Alignment
AlignLeft
toAlignment Char
'>' = Alignment
AlignRight
toAlignment Char
'=' = Alignment
AlignCenter
toAlignment Char
_ = Alignment
AlignDefault
cellAttributes :: PandocMonad m => TextileParser m (Bool, Alignment)
cellAttributes :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Bool, Alignment)
cellAttributes = ParsecT Sources ParserState m (Bool, Alignment)
-> ParsecT Sources ParserState m (Bool, Alignment)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Bool, Alignment)
-> ParsecT Sources ParserState m (Bool, Alignment))
-> ParsecT Sources ParserState m (Bool, Alignment)
-> ParsecT Sources ParserState m (Bool, Alignment)
forall a b. (a -> b) -> a -> b
$ do
Bool
isHeader <- Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Bool
False (Bool
True Bool
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'_')
ParsecT Sources ParserState m [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]
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ 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
oneOf [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
>> 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]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit
Alignment
alignment <- Alignment
-> ParsecT Sources ParserState m Alignment
-> ParsecT Sources ParserState m Alignment
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Alignment
AlignDefault (ParsecT Sources ParserState m Alignment
-> ParsecT Sources ParserState m Alignment)
-> ParsecT Sources ParserState m Alignment
-> ParsecT Sources ParserState m Alignment
forall a b. (a -> b) -> a -> b
$ Char -> Alignment
toAlignment (Char -> Alignment)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Alignment
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
oneOf [Char]
"<>="
Attr
_ <- TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
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
'.'
(Bool, Alignment)
-> ParsecT Sources ParserState m (Bool, Alignment)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
isHeader, Alignment
alignment)
tableCell :: PandocMonad m => TextileParser m ((Bool, Alignment), Blocks)
tableCell :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m ((Bool, Alignment), Many Block)
tableCell = ParsecT Sources ParserState m ((Bool, Alignment), Many Block)
-> ParsecT Sources ParserState m ((Bool, Alignment), Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ((Bool, Alignment), Many Block)
-> ParsecT Sources ParserState m ((Bool, Alignment), Many Block))
-> ParsecT Sources ParserState m ((Bool, Alignment), Many Block)
-> ParsecT Sources ParserState m ((Bool, Alignment), Many Block)
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
'|'
(Bool
isHeader, Alignment
alignment) <- (Bool, Alignment)
-> ParsecT Sources ParserState m (Bool, Alignment)
-> ParsecT Sources ParserState m (Bool, Alignment)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Bool
False, Alignment
AlignDefault) ParsecT Sources ParserState m (Bool, Alignment)
forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Bool, Alignment)
cellAttributes
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
Text
raw <- Text -> Text
trim (Text -> Text) -> ([Char] -> Text) -> [Char] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ([Char] -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"|\n" ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline))
Inlines
content <- [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]
-> 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
-> ParsecT Sources ParserState m [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
inline) Text
raw
((Bool, Alignment), Many Block)
-> ParsecT Sources ParserState m ((Bool, Alignment), Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool
isHeader, Alignment
alignment), Inlines -> Many Block
B.plain Inlines
content)
tableRow :: PandocMonad m => TextileParser m [((Bool, Alignment), Blocks)]
tableRow :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m [((Bool, Alignment), Many Block)]
tableRow = ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)])
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char])
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall a b. (a -> b) -> a -> b
$ do
Attr
_ <- TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
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
'.'
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]
many1 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 ((Bool, Alignment), Many Block)
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
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 ((Bool, Alignment), Many Block)
forall (m :: * -> *).
PandocMonad m =>
TextileParser m ((Bool, Alignment), Many Block)
tableCell ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
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
'|' ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
table :: PandocMonad m => TextileParser m Blocks
table :: forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
table = ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block))
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ do
Inlines
caption <- Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty (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
-> 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]
string [Char]
"table"
Attr
_ <- TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
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
'.'
Text
rawcapt <- Text -> Text
trim (Text -> Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
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' ([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 [Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
inline) Text
rawcapt
[[((Bool, Alignment), Many Block)]]
rawrows <- ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
-> ParsecT
Sources ParserState m [[((Bool, Alignment), Many Block)]]
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 [((Bool, Alignment), Many Block)]
-> ParsecT
Sources ParserState m [[((Bool, Alignment), Many Block)]])
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
-> ParsecT
Sources ParserState m [[((Bool, Alignment), Many Block)]]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => TextileParser m ()
ignorableRow ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
-> ParsecT Sources ParserState m [((Bool, Alignment), Many Block)]
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 [((Bool, Alignment), Many Block)]
forall (m :: * -> *).
PandocMonad m =>
TextileParser m [((Bool, Alignment), Many Block)]
tableRow
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => TextileParser m ()
ignorableRow
ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
let ([((Bool, Alignment), Many Block)]
headers, [[((Bool, Alignment), Many Block)]]
rows) = case [[((Bool, Alignment), Many Block)]]
rawrows of
([((Bool, Alignment), Many Block)]
toprow:[[((Bool, Alignment), Many Block)]]
rest) | (((Bool, Alignment), Many Block) -> Bool)
-> [((Bool, Alignment), Many Block)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Bool, Alignment) -> Bool
forall a b. (a, b) -> a
fst ((Bool, Alignment) -> Bool)
-> (((Bool, Alignment), Many Block) -> (Bool, Alignment))
-> ((Bool, Alignment), Many Block)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Bool, Alignment), Many Block) -> (Bool, Alignment)
forall a b. (a, b) -> a
fst) [((Bool, Alignment), Many Block)]
toprow ->
([((Bool, Alignment), Many Block)]
toprow, [[((Bool, Alignment), Many Block)]]
rest)
[[((Bool, Alignment), Many Block)]]
_ -> ([((Bool, Alignment), Many Block)]
forall a. Monoid a => a
mempty, [[((Bool, Alignment), Many Block)]]
rawrows)
let nbOfCols :: Int
nbOfCols = NonEmpty Int -> Int
forall a. Ord a => NonEmpty a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (NonEmpty Int -> Int) -> NonEmpty Int -> Int
forall a b. (a -> b) -> a -> b
$ ([((Bool, Alignment), Many Block)] -> Int)
-> NonEmpty [((Bool, Alignment), Many Block)] -> NonEmpty Int
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [((Bool, Alignment), Many Block)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([((Bool, Alignment), Many Block)]
headers [((Bool, Alignment), Many Block)]
-> [[((Bool, Alignment), Many Block)]]
-> NonEmpty [((Bool, Alignment), Many Block)]
forall a. a -> [a] -> NonEmpty a
:| [[((Bool, Alignment), Many Block)]]
rows)
let aligns :: [Alignment]
aligns = ([Alignment] -> Alignment) -> [[Alignment]] -> [Alignment]
forall a b. (a -> b) -> [a] -> [b]
map (Alignment
-> (NonEmpty Alignment -> Alignment)
-> Maybe (NonEmpty Alignment)
-> Alignment
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Alignment
AlignDefault NonEmpty Alignment -> Alignment
forall a. Ord a => NonEmpty a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum (Maybe (NonEmpty Alignment) -> Alignment)
-> ([Alignment] -> Maybe (NonEmpty Alignment))
-> [Alignment]
-> Alignment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Alignment] -> Maybe (NonEmpty Alignment)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty) ([[Alignment]] -> [Alignment]) -> [[Alignment]] -> [Alignment]
forall a b. (a -> b) -> a -> b
$
[[Alignment]] -> [[Alignment]]
forall a. [[a]] -> [[a]]
transpose ([[Alignment]] -> [[Alignment]]) -> [[Alignment]] -> [[Alignment]]
forall a b. (a -> b) -> a -> b
$ ([((Bool, Alignment), Many Block)] -> [Alignment])
-> [[((Bool, Alignment), Many Block)]] -> [[Alignment]]
forall a b. (a -> b) -> [a] -> [b]
map ((((Bool, Alignment), Many Block) -> Alignment)
-> [((Bool, Alignment), Many Block)] -> [Alignment]
forall a b. (a -> b) -> [a] -> [b]
map ((Bool, Alignment) -> Alignment
forall a b. (a, b) -> b
snd ((Bool, Alignment) -> Alignment)
-> (((Bool, Alignment), Many Block) -> (Bool, Alignment))
-> ((Bool, Alignment), Many Block)
-> Alignment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Bool, Alignment), Many Block) -> (Bool, Alignment)
forall a b. (a, b) -> a
fst)) ([((Bool, Alignment), Many Block)]
headers[((Bool, Alignment), Many Block)]
-> [[((Bool, Alignment), Many Block)]]
-> [[((Bool, Alignment), Many Block)]]
forall a. a -> [a] -> [a]
:[[((Bool, Alignment), Many Block)]]
rows)
let toRow :: [Many Block] -> Row
toRow = Attr -> [Cell] -> Row
Row Attr
nullAttr ([Cell] -> Row) -> ([Many Block] -> [Cell]) -> [Many Block] -> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Many Block -> Cell) -> [Many Block] -> [Cell]
forall a b. (a -> b) -> [a] -> [b]
map Many Block -> Cell
B.simpleCell
toHeaderRow :: [Many Block] -> [Row]
toHeaderRow [Many Block]
l = [[Many Block] -> Row
toRow [Many Block]
l | Bool -> Bool
not ([Many Block] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Many Block]
l)]
Many Block -> ParsecT Sources ParserState m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Block -> ParsecT Sources ParserState m (Many Block))
-> Many Block -> ParsecT Sources ParserState m (Many Block)
forall a b. (a -> b) -> a -> b
$ Caption
-> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Many Block
B.table (Many Block -> Caption
B.simpleCaption (Many Block -> Caption) -> Many Block -> Caption
forall a b. (a -> b) -> a -> b
$ Inlines -> Many Block
B.plain Inlines
caption)
([Alignment] -> [ColWidth] -> [ColSpec]
forall a b. [a] -> [b] -> [(a, b)]
zip [Alignment]
aligns (Int -> ColWidth -> [ColWidth]
forall a. Int -> a -> [a]
replicate Int
nbOfCols ColWidth
ColWidthDefault))
(Attr -> [Row] -> TableHead
TableHead Attr
nullAttr ([Row] -> TableHead) -> [Row] -> TableHead
forall a b. (a -> b) -> a -> b
$ [Many Block] -> [Row]
toHeaderRow ([Many Block] -> [Row]) -> [Many Block] -> [Row]
forall a b. (a -> b) -> a -> b
$ (((Bool, Alignment), Many Block) -> Many Block)
-> [((Bool, Alignment), Many Block)] -> [Many Block]
forall a b. (a -> b) -> [a] -> [b]
map ((Bool, Alignment), Many Block) -> Many Block
forall a b. (a, b) -> b
snd [((Bool, Alignment), Many Block)]
headers)
[Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] ([Row] -> TableBody) -> [Row] -> TableBody
forall a b. (a -> b) -> a -> b
$ ([((Bool, Alignment), Many Block)] -> Row)
-> [[((Bool, Alignment), Many Block)]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map ([Many Block] -> Row
toRow ([Many Block] -> Row)
-> ([((Bool, Alignment), Many Block)] -> [Many Block])
-> [((Bool, Alignment), Many Block)]
-> Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((Bool, Alignment), Many Block) -> Many Block)
-> [((Bool, Alignment), Many Block)] -> [Many Block]
forall a b. (a -> b) -> [a] -> [b]
map ((Bool, Alignment), Many Block) -> Many Block
forall a b. (a, b) -> b
snd) [[((Bool, Alignment), Many Block)]]
rows]
(Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr [])
ignorableRow :: PandocMonad m => TextileParser m ()
ignorableRow :: forall (m :: * -> *). PandocMonad m => TextileParser m ()
ignorableRow = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|'
[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
oneOf [Char]
":^-~"
Attr
_ <- TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
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
'.'
Text
_ <- ParsecT Sources ParserState m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
() -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
explicitBlockStart :: PandocMonad m => Text -> TextileParser m Attr
explicitBlockStart :: forall (m :: * -> *). PandocMonad m => Text -> TextileParser m Attr
explicitBlockStart Text
name = ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr)
-> ParsecT Sources ParserState m Attr
-> ParsecT Sources ParserState m Attr
forall a b. (a -> b) -> a -> b
$ do
[Char] -> ParsecT Sources ParserState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string (Text -> [Char]
T.unpack Text
name)
Attr
attr <- ParsecT Sources ParserState m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
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
'.'
ParsecT Sources ParserState m Inlines
-> 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 Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace
ParsecT Sources ParserState m Inlines
-> 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 Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
endline
Attr -> ParsecT Sources ParserState m Attr
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Attr
attr
explicitBlock :: PandocMonad m
=> Text
-> TextileParser m Blocks
-> TextileParser m Blocks
explicitBlock :: forall (m :: * -> *).
PandocMonad m =>
Text
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
explicitBlock Text
name TextileParser m (Many Block)
blk = TextileParser m (Many Block) -> TextileParser m (Many Block)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TextileParser m (Many Block) -> TextileParser m (Many Block))
-> TextileParser m (Many Block) -> TextileParser m (Many Block)
forall a b. (a -> b) -> a -> b
$ do
Attr
attr <- Text -> TextileParser m Attr
forall (m :: * -> *). PandocMonad m => Text -> TextileParser m Attr
explicitBlockStart Text
name
Many Block
contents <- TextileParser m (Many Block)
blk
Many Block -> TextileParser m (Many Block)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Many Block -> TextileParser m (Many Block))
-> Many Block -> TextileParser m (Many Block)
forall a b. (a -> b) -> a -> b
$ if Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
nullAttr
then Many Block
contents
else Attr -> Many Block -> Many Block
B.divWith Attr
attr Many Block
contents
inline :: PandocMonad m => TextileParser m Inlines
inline :: forall (m :: * -> *). PandocMonad m => TextileParser 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 => [TextileParser m Inlines]
inlineParsers ParsecT Sources ParserState m Inlines
-> [Char] -> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> [Char] -> ParsecT s u m a
<?> [Char]
"inline"
inlineParsers :: PandocMonad m => [TextileParser m Inlines]
inlineParsers :: forall (m :: * -> *). PandocMonad m => [TextileParser m Inlines]
inlineParsers = [ TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
str
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
endline
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
code
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
escapedInline
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
inlineMarkup
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
groupedInlineMarkup
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
rawHtmlInline
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
rawLaTeXInline'
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
note
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
link
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
image
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
mark
, Text -> Inlines
B.str (Text -> Inlines)
-> ParsecT Sources ParserState m Text -> TextileParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
characterReference
, TextileParser m Inlines -> TextileParser 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 TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
inline
, TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
symbol
]
inlineMarkup :: PandocMonad m => TextileParser m Inlines
inlineMarkup :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
inlineMarkup = [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 [ TextileParser m [Char]
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline ([Char] -> TextileParser m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"??") ([Citation] -> Inlines -> Inlines
B.cite [])
, TextileParser m [Char]
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline ([Char] -> TextileParser m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"**") Inlines -> Inlines
B.strong
, TextileParser m [Char]
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline ([Char] -> TextileParser m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"__") Inlines -> Inlines
B.emph
, TextileParser m Char
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline (Char -> TextileParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*') Inlines -> Inlines
B.strong
, TextileParser m Char
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline (Char -> TextileParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'_') Inlines -> Inlines
B.emph
, TextileParser m Char
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline (Char -> TextileParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'+') Inlines -> Inlines
B.underline
, TextileParser m Char
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline (Char -> TextileParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-' TextileParser m Char
-> ParsecT Sources ParserState m () -> TextileParser 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
<* TextileParser 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 -> TextileParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-')) Inlines -> Inlines
B.strikeout
, TextileParser m Char
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline (Char -> TextileParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'^') Inlines -> Inlines
B.superscript
, TextileParser m Char
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline (Char -> TextileParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'~') Inlines -> Inlines
B.subscript
, TextileParser m Char
-> (Inlines -> Inlines) -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline (Char -> TextileParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'%') Inlines -> Inlines
forall a. a -> a
id
]
mark :: PandocMonad m => TextileParser m Inlines
mark :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
mark = 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
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'(' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (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
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
tm 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
-> 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
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
reg 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 => TextileParser m Inlines
copy)
reg :: PandocMonad m => TextileParser m Inlines
reg :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
reg = 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
oneOf [Char]
"Rr"
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 -> TextileParser m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TextileParser m Inlines)
-> Inlines -> TextileParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
"\174"
tm :: PandocMonad m => TextileParser m Inlines
tm :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
tm = 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
oneOf [Char]
"Tt"
[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
oneOf [Char]
"Mm"
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 -> TextileParser m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TextileParser m Inlines)
-> Inlines -> TextileParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
"\8482"
copy :: PandocMonad m => TextileParser m Inlines
copy :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
copy = 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
oneOf [Char]
"Cc"
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 -> TextileParser m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TextileParser m Inlines)
-> Inlines -> TextileParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
"\169"
note :: PandocMonad m => TextileParser m Inlines
note :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
note = 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]
ref <- 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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit ParsecT Sources ParserState m [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 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
']'
NoteTable
notes <- ParserState -> NoteTable
stateNotes (ParserState -> NoteTable)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m NoteTable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
case Text -> NoteTable -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup ([Char] -> Text
T.pack [Char]
ref) NoteTable
notes of
Maybe Text
Nothing -> [Char] -> ParsecT Sources ParserState m Inlines
forall a. [Char] -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
Prelude.fail [Char]
"note not found"
Just Text
raw -> Many Block -> Inlines
B.note (Many Block -> Inlines)
-> ParsecT Sources ParserState m (Many Block)
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m (Many Block)
-> Text -> ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *) u a.
(Monad m, HasLastStrPosition u) =>
ParsecT Sources u m a -> Text -> ParsecT Sources u m a
parseFromString' ParsecT Sources ParserState m (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
parseBlocks Text
raw
markupChars :: [Char]
markupChars :: [Char]
markupChars = [Char]
"\\*#_@~-+^|%=[]&"
stringBreakers :: [Char]
stringBreakers :: [Char]
stringBreakers = [Char]
" \t\n\r.,\"'?!;:<>«»„“”‚‘’()[]"
wordBoundaries :: [Char]
wordBoundaries :: [Char]
wordBoundaries = [Char]
markupChars [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
stringBreakers
hyphenedWords :: PandocMonad m => TextileParser m Text
hyphenedWords :: forall (m :: * -> *). PandocMonad m => TextileParser m Text
hyphenedWords = do
Text
x <- TextileParser m Text
forall (m :: * -> *). PandocMonad m => TextileParser m Text
wordChunk
[Text]
xs <- TextileParser m Text -> ParsecT Sources ParserState m [Text]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (TextileParser m Text -> TextileParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TextileParser m Text -> TextileParser m Text)
-> TextileParser m Text -> TextileParser m Text
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-' ParsecT Sources ParserState m Char
-> TextileParser m Text -> TextileParser 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
>> TextileParser m Text
forall (m :: * -> *). PandocMonad m => TextileParser m Text
wordChunk)
Text -> TextileParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> TextileParser m Text) -> Text -> TextileParser m Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
T.intercalate Text
"-" (Text
xText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
xs)
wordChunk :: PandocMonad m => TextileParser m Text
wordChunk :: forall (m :: * -> *). PandocMonad m => TextileParser m Text
wordChunk = ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ do
Char
hd <- [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
noneOf [Char]
wordBoundaries
[Char]
tl <- 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]
many ( [Char] -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
wordBoundaries ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
note 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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [Char] -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
markupChars
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 a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ([Char] -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
wordBoundaries) ) )
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
$ [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ Char
hdChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
tl
str :: PandocMonad m => TextileParser m Inlines
str :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
str = do
Text
baseStr <- TextileParser m Text
forall (m :: * -> *). PandocMonad m => TextileParser m Text
hyphenedWords
Text
fullStr <- Text -> TextileParser m Text -> TextileParser m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
baseStr (TextileParser m Text -> TextileParser m Text)
-> TextileParser m Text -> TextileParser m Text
forall a b. (a -> b) -> a -> b
$ TextileParser m Text -> TextileParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TextileParser m Text -> TextileParser m Text)
-> TextileParser m Text -> TextileParser m Text
forall a b. (a -> b) -> a -> b
$ do
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isUpper Text
baseStr
Text
acro <- [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char] -> TextileParser 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 Char
-> ParsecT Sources ParserState m [Char]
forall end s (m :: * -> *) st t a.
(Show end, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m t
-> ParsecT s st m end -> ParsecT s st m a -> ParsecT s st m [a]
enclosed (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'(') (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
')') ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TextileParser m Char
anyChar'
Text -> TextileParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> TextileParser m Text) -> Text -> TextileParser m Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text
baseStr, Text
" (", Text
acro, Text
")"]
ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos
Inlines -> TextileParser m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TextileParser m Inlines)
-> Inlines -> TextileParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
fullStr
whitespace :: PandocMonad m => TextileParser m Inlines
whitespace :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace = 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]
many1 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 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 ParsecT Sources ParserState m Inlines
-> [Char] -> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> [Char] -> ParsecT s u m a
<?> [Char]
"whitespace"
endline :: PandocMonad m => TextileParser m Inlines
endline :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
endline = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => TextileParser m ()
listStart
ParsecT Sources ParserState m (Many Block)
-> 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 (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
rawHtmlBlock
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
rawHtmlInline :: PandocMonad m => TextileParser m Inlines
rawHtmlInline :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
rawHtmlInline = Text -> Text -> Inlines
B.rawInline Text
"html" (Text -> Inlines)
-> ((Tag Text, Text) -> Text) -> (Tag Text, Text) -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tag Text, Text) -> Text
forall a b. (a, b) -> b
snd ((Tag Text, Text) -> Inlines)
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag Tag Text -> Bool
isInlineTag
rawLaTeXInline' :: PandocMonad m => TextileParser m Inlines
rawLaTeXInline' :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
rawLaTeXInline' = 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
Extension -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_tex
Text -> Text -> Inlines
B.rawInline Text
"latex" (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
ParsecT Sources s m Text
rawLaTeXInline
link :: PandocMonad m => TextileParser m Inlines
link :: forall (m :: * -> *). PandocMonad m => TextileParser 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
Bool
bracketed <- (Bool
True Bool
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Bool
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'[') ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
-> ParsecT Sources ParserState m Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT Sources ParserState m Bool
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
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 Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ([Char] -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
" \t\n\r")
Attr
attr <- TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
attributes
Inlines
name <- Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
QuoteContext
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m [Inlines]
forall s a.
QuoteContext
-> ParsecT s ParserState m a -> ParsecT s ParserState m a
forall st (m :: * -> *) s a.
HasQuoteContext st m =>
QuoteContext -> ParsecT s st m a -> ParsecT s st m a
withQuoteContext QuoteContext
InDoubleQuote (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 => TextileParser m Inlines
inline (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'))
Text
url <- Bool -> TextileParser m Text
forall (m :: * -> *). PandocMonad m => Bool -> TextileParser m Text
linkUrl Bool
bracketed
let name' :: Inlines
name' = if Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
name [Inline] -> [Inline] -> Bool
forall a. Eq a => a -> a -> Bool
== [Text -> Inline
Str Text
"$"] then Text -> Inlines
B.str Text
url else Inlines
name
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
$ if Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
nullAttr
then Text -> Text -> Inlines -> Inlines
B.link Text
url Text
"" Inlines
name'
else Attr -> Inlines -> Inlines
B.spanWith Attr
attr (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link Text
url Text
"" Inlines
name'
linkUrl :: PandocMonad m => Bool -> TextileParser m Text
linkUrl :: forall (m :: * -> *). PandocMonad m => Bool -> TextileParser m Text
linkUrl Bool
bracketed = 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
':'
let stop :: ParsecT Sources u m Char
stop = if Bool
bracketed
then Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']'
else ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources u m Char -> ParsecT Sources u m Char)
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
space 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. Monad m => ParsecT Sources s m Char
eof' 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
<|> [Char] -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
"[]" 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 -> ParsecT Sources u m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char] -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
(ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
space 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 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. Monad m => ParsecT Sources s m Char
eof'))
Text
rawLink <- [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char] -> TextileParser 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 [Char]
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 s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
stop
ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Text -> TextileParser m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> TextileParser m Text) -> Text -> TextileParser m Text
forall a b. (a -> b) -> a -> b
$ case Key -> KeyTable -> Maybe ((Text, Text), Attr)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> Key
toKey Text
rawLink) (ParserState -> KeyTable
stateKeys ParserState
st) of
Maybe ((Text, Text), Attr)
Nothing -> Text
rawLink
Just ((Text
src, Text
_), Attr
_) -> Text
src
image :: PandocMonad m => TextileParser m Inlines
image :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
image = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'!' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> 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
space
(Text
ident, [Text]
cls, NoteTable
kvs) <- TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
attributes
let attr :: Attr
attr = case Text -> NoteTable -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"style" NoteTable
kvs of
Just Text
stls -> (Text
ident, [Text]
cls, [Text] -> Text -> NoteTable
pickStylesToKVs [Text
"width", Text
"height"] Text
stls)
Maybe Text
Nothing -> (Text
ident, [Text]
cls, NoteTable
kvs)
Text
src <- [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> 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]
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
noneOf [Char]
" \t\n\r!(")
Text
alt <- ([Char] -> Text)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Text
T.pack (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ [Char]
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [Char]
"" (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char])
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m [Char]
-> 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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources 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
')')
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'!'
let img :: Inlines
img = Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith Attr
attr Text
src Text
alt (Text -> Inlines
B.str Text
alt)
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 (do
Text
url <- Bool -> ParsecT Sources ParserState m Text
forall (m :: * -> *). PandocMonad m => Bool -> TextileParser m Text
linkUrl Bool
False
Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Inlines -> Inlines
B.link Text
url Text
"" Inlines
img))
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
<|> Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
img
escapedInline :: PandocMonad m => TextileParser m Inlines
escapedInline :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
escapedInline = TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
escapedEqs TextileParser m Inlines
-> TextileParser m Inlines -> TextileParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
escapedTag
escapedEqs :: PandocMonad m => TextileParser m Inlines
escapedEqs :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
escapedEqs = Text -> Inlines
B.str (Text -> Inlines) -> ([Char] -> Text) -> [Char] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Inlines)
-> ParsecT Sources ParserState m [Char]
-> 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 [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char] -> ParsecT Sources ParserState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TextileParser m Char
anyChar' (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char])
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall a b. (a -> b) -> a -> b
$ [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]
string [Char]
"=="))
escapedTag :: PandocMonad m => TextileParser m Inlines
escapedTag :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
escapedTag = Text -> Inlines
B.str (Text -> Inlines) -> ([Char] -> Text) -> [Char] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Inlines)
-> ParsecT Sources ParserState m [Char]
-> 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 [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char] -> ParsecT Sources ParserState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"<notextile>" ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TextileParser m Char
anyChar' (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char])
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall a b. (a -> b) -> a -> b
$ [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]
string [Char]
"</notextile>"))
symbol :: PandocMonad m => TextileParser m Inlines
symbol :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
symbol = do
Char
c <- 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 ()
-> 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 (Many Block)
-> 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 (Many Block)
forall (m :: * -> *). PandocMonad m => TextileParser m (Many Block)
rawHtmlBlock 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 (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
[Char] -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
wordBoundaries
ParsecT Sources ParserState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos
Inlines -> TextileParser m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> TextileParser m Inlines)
-> Inlines -> TextileParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> (Char -> Text) -> Char -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton (Char -> Inlines) -> Char -> Inlines
forall a b. (a -> b) -> a -> b
$ Char
c
code :: PandocMonad m => TextileParser m Inlines
code :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
code = TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
code1 TextileParser m Inlines
-> TextileParser m Inlines -> TextileParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TextileParser m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
code2
anyChar' :: PandocMonad m => TextileParser m Char
anyChar' :: forall (m :: * -> *). PandocMonad m => TextileParser m Char
anyChar' =
(Char -> Bool) -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'\n') ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\n' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline)
code1 :: PandocMonad m => TextileParser m Inlines
code1 :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
code1 = Text -> Inlines
B.code (Text -> Inlines) -> ([Char] -> Text) -> [Char] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Inlines)
-> ParsecT Sources ParserState m [Char]
-> 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 Char
-> ParsecT Sources ParserState m [Char]
forall (m :: * -> *) t st a.
(PandocMonad m, Show t) =>
ParsecT Sources st m t
-> ParsecT Sources st m a -> ParsecT Sources st m [a]
surrounded (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'@') ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TextileParser m Char
anyChar'
code2 :: PandocMonad m => TextileParser m Inlines
code2 :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
code2 = do
(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 ((Text -> Bool) -> (NoteTable -> Bool) -> Tag Text -> Bool
forall str.
(str -> Bool) -> ([Attribute str] -> Bool) -> Tag str -> Bool
tagOpen (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"tt") NoteTable -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null)
Text -> Inlines
B.code (Text -> Inlines) -> ([Char] -> Text) -> [Char] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Text
T.pack ([Char] -> Inlines)
-> ParsecT Sources ParserState m [Char] -> TextileParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TextileParser m Char
anyChar' (ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text, Text))
-> ParsecT Sources ParserState m (Tag Text, Text)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall a b. (a -> b) -> a -> b
$ (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall st (m :: * -> *).
(HasReaderOptions st, Monad m) =>
(Tag Text -> Bool) -> ParsecT Sources st m (Tag Text, Text)
htmlTag ((Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text))
-> (Tag Text -> Bool)
-> ParsecT Sources ParserState m (Tag Text, Text)
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> Tag Text -> Bool
forall str. (str -> Bool) -> Tag str -> Bool
tagClose (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
"tt"))
orderedListStartAttr :: PandocMonad m => TextileParser m Int
orderedListStartAttr :: forall (m :: * -> *). PandocMonad m => TextileParser m Int
orderedListStartAttr = do
[Char]
digits <- 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]
many ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit
case [Char] -> Maybe Int
forall a. Read a => [Char] -> Maybe a
readMaybe [Char]
digits :: Maybe Int of
Maybe Int
Nothing -> Int -> TextileParser m Int
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
1
Just Int
n -> Int -> TextileParser m Int
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
n
attributes :: PandocMonad m => TextileParser m Attr
attributes :: forall (m :: * -> *). PandocMonad m => TextileParser m Attr
attributes = (Attr -> (Attr -> Attr) -> Attr) -> Attr -> [Attr -> Attr] -> Attr
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (((Attr -> Attr) -> Attr -> Attr) -> Attr -> (Attr -> Attr) -> Attr
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Attr -> Attr) -> Attr -> Attr
forall a b. (a -> b) -> a -> b
($)) (Text
"",[],[]) ([Attr -> Attr] -> Attr)
-> ParsecT Sources ParserState m [Attr -> Attr]
-> ParsecT Sources ParserState m Attr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT Sources ParserState m [Attr -> Attr]
-> ParsecT Sources ParserState m [Attr -> Attr]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (do Attr -> Attr
special <- (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Attr -> Attr
forall a. a -> a
id ParsecT Sources ParserState m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
specialAttribute
[Attr -> Attr]
attrs <- ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m [Attr -> Attr]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
attribute
[Attr -> Attr] -> ParsecT Sources ParserState m [Attr -> Attr]
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Attr -> Attr
special (Attr -> Attr) -> [Attr -> Attr] -> [Attr -> Attr]
forall a. a -> [a] -> [a]
: [Attr -> Attr]
attrs))
specialAttribute :: PandocMonad m => TextileParser m (Attr -> Attr)
specialAttribute :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
specialAttribute = do
[Char]
alignStr <- ([Char]
"center" [Char]
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'=') ParsecT Sources ParserState m [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]
"justify" [Char]
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char] -> ParsecT Sources ParserState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"<>")) ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
([Char]
"right" [Char]
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>') ParsecT Sources ParserState m [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]
"left" [Char]
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<')
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
(Attr -> Attr) -> TextileParser m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> TextileParser m (Attr -> Attr))
-> (Attr -> Attr) -> TextileParser m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ Text -> Attr -> Attr
addStyle (Text -> Attr -> Attr) -> Text -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack ([Char] -> Text) -> [Char] -> Text
forall a b. (a -> b) -> a -> b
$ [Char]
"text-align:" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
alignStr
attribute :: PandocMonad m => TextileParser m (Attr -> Attr)
attribute :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
attribute = ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr))
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$
(ParsecT Sources ParserState m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
classIdAttr ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
styleAttr ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m (Attr -> Attr)
forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
langAttr) ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
classIdAttr :: PandocMonad m => TextileParser m (Attr -> Attr)
classIdAttr :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
classIdAttr = ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr))
-> ParsecT Sources ParserState m (Attr -> Attr)
-> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'('
[Text]
ws <- Text -> [Text]
T.words (Text -> [Text]) -> ([Char] -> Text) -> [Char] -> [Text]
forall a b. (a -> b) -> ([Char] -> a) -> [Char] -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` [Char] -> Text
T.pack ([Char] -> [Text])
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TextileParser 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
')')
case [Text] -> [Text]
forall a. [a] -> [a]
reverse [Text]
ws of
[]
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr))
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ \(Text
_,[Text]
_,NoteTable
keyvals) -> (Text
"",[],NoteTable
keyvals)
((Text -> Maybe (Char, Text)
T.uncons -> Just (Char
'#', Text
ident')):[Text]
classes')
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr))
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ \(Text
_,[Text]
_,NoteTable
keyvals) -> (Text
ident',[Text]
classes',NoteTable
keyvals)
[Text]
classes'
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr))
-> (Attr -> Attr) -> ParsecT Sources ParserState m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ \(Text
_,[Text]
_,NoteTable
keyvals) -> (Text
"",[Text]
classes',NoteTable
keyvals)
styleAttr :: PandocMonad m => TextileParser m (Attr -> Attr)
styleAttr :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
styleAttr = do
[Char]
style <- ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char])
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall end s (m :: * -> *) st t a.
(Show end, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m t
-> ParsecT s st m end -> ParsecT s st m a -> ParsecT s st m [a]
enclosed (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'{') (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'}') ParsecT Sources ParserState m Char
forall (m :: * -> *). PandocMonad m => TextileParser m Char
anyChar'
(Attr -> Attr) -> TextileParser m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> TextileParser m (Attr -> Attr))
-> (Attr -> Attr) -> TextileParser m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ Text -> Attr -> Attr
addStyle (Text -> Attr -> Attr) -> Text -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
T.pack [Char]
style
addStyle :: Text -> Attr -> Attr
addStyle :: Text -> Attr -> Attr
addStyle Text
style (Text
id',[Text]
classes,NoteTable
keyvals) =
(Text
id',[Text]
classes,NoteTable
keyvals')
where keyvals' :: NoteTable
keyvals' = (Text
"style", Text
style') (Text, Text) -> NoteTable -> NoteTable
forall a. a -> [a] -> [a]
: [(Text
k,Text
v) | (Text
k,Text
v) <- NoteTable
keyvals, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"style"]
style' :: Text
style' = Text
style Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
";" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.concat [Text
v | (Text
"style",Text
v) <- NoteTable
keyvals]
langAttr :: PandocMonad m => TextileParser m (Attr -> Attr)
langAttr :: forall (m :: * -> *).
PandocMonad m =>
TextileParser m (Attr -> Attr)
langAttr = do
[Char]
lang <- ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char])
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m [Char]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Char]
forall end s (m :: * -> *) st t a.
(Show end, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m t
-> ParsecT s st m end -> ParsecT s st m a -> ParsecT s st m [a]
enclosed (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'[') (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']') ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum
(Attr -> Attr) -> TextileParser m (Attr -> Attr)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Attr -> Attr) -> TextileParser m (Attr -> Attr))
-> (Attr -> Attr) -> TextileParser m (Attr -> Attr)
forall a b. (a -> b) -> a -> b
$ \(Text
id',[Text]
classes,NoteTable
keyvals) -> (Text
id',[Text]
classes,(Text
"lang",[Char] -> Text
T.pack [Char]
lang)(Text, Text) -> NoteTable -> NoteTable
forall a. a -> [a] -> [a]
:NoteTable
keyvals)
surrounded :: (PandocMonad m, Show t)
=> ParsecT Sources st m t
-> ParsecT Sources st m a
-> ParsecT Sources st m [a]
surrounded :: forall (m :: * -> *) t st a.
(PandocMonad m, Show t) =>
ParsecT Sources st m t
-> ParsecT Sources st m a -> ParsecT Sources st m [a]
surrounded ParsecT Sources st m t
border =
ParsecT Sources st m ()
-> ParsecT Sources st m t
-> ParsecT Sources st m a
-> ParsecT Sources st m [a]
forall end s (m :: * -> *) st t a.
(Show end, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m t
-> ParsecT s st m end -> ParsecT s st m a -> ParsecT s st m [a]
enclosed (ParsecT Sources st m t
border ParsecT Sources st m t
-> ParsecT Sources st m () -> ParsecT Sources st m ()
forall a b.
ParsecT Sources st m a
-> ParsecT Sources st m b -> ParsecT Sources st m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources st m Char -> ParsecT Sources st m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ([Char] -> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
" \t\n\r")) (ParsecT Sources st m t -> ParsecT Sources st m t
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources st m t
border)
simpleInline :: PandocMonad m
=> TextileParser m t
-> (Inlines -> Inlines)
-> TextileParser m Inlines
simpleInline :: forall (m :: * -> *) t.
PandocMonad m =>
TextileParser m t
-> (Inlines -> Inlines) -> TextileParser m Inlines
simpleInline TextileParser m t
border Inlines -> Inlines
construct = 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
ParsecT Sources ParserState m Bool
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m Bool
notAfterString
TextileParser m t
border TextileParser m t
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ([Char] -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
" \t\n\r")
Attr
attr <- TextileParser m Attr
forall (m :: * -> *). PandocMonad m => TextileParser m Attr
attributes
Inlines
body <- Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
QuoteContext
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m [Inlines]
forall s a.
QuoteContext
-> ParsecT s ParserState m a -> ParsecT s ParserState m a
forall st (m :: * -> *) s a.
HasQuoteContext st m =>
QuoteContext -> ParsecT s st m a -> ParsecT s st m a
withQuoteContext QuoteContext
InSingleQuote
(ParsecT Sources ParserState m Inlines
-> TextileParser m t -> 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 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 (m :: * -> *). PandocMonad m => TextileParser m Inlines
inline)
(TextileParser m t -> TextileParser m t
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try TextileParser m t
border TextileParser m t
-> ParsecT Sources ParserState m () -> TextileParser m t
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum))
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
$ Inlines -> Inlines
construct (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$
if Attr
attr Attr -> Attr -> Bool
forall a. Eq a => a -> a -> Bool
== Attr
nullAttr
then Inlines
body
else Attr -> Inlines -> Inlines
B.spanWith Attr
attr Inlines
body
groupedInlineMarkup :: PandocMonad m => TextileParser m Inlines
groupedInlineMarkup :: forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
groupedInlineMarkup = 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
'['
Inlines
sp1 <- Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty (ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
B.space Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace
Inlines
result <- QuoteContext
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s a.
QuoteContext
-> ParsecT s ParserState m a -> ParsecT s ParserState m a
forall st (m :: * -> *) s a.
HasQuoteContext st m =>
QuoteContext -> ParsecT s st m a -> ParsecT s st m a
withQuoteContext QuoteContext
InSingleQuote ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
inlineMarkup
Inlines
sp2 <- Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty (ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
B.space Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TextileParser m Inlines
whitespace
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
$ Inlines
sp1 Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
result Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
sp2
eof' :: Monad m => ParsecT Sources s m Char
eof' :: forall (m :: * -> *) s. Monad m => ParsecT Sources s m Char
eof' = Char
'\n' Char -> ParsecT Sources s m () -> ParsecT Sources s m Char
forall a b. a -> ParsecT Sources s m b -> ParsecT Sources s m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources s m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof