{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.Creole ( readCreole
) where
import Control.Monad
import Control.Monad.Except (throwError)
import qualified Data.Foldable as F
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (enclosed)
readCreole :: (PandocMonad m, ToSources a)
=> ReaderOptions
-> a
-> m Pandoc
readCreole :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readCreole ReaderOptions
opts a
s = do
let sources :: Sources
sources = Int -> Sources -> Sources
ensureFinalNewlines Int
2 (a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s)
Either PandocError Pandoc
res <- ParsecT Sources ParserState m Pandoc
-> ParserState -> Sources -> m (Either PandocError Pandoc)
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParsecT Sources ParserState m Pandoc
forall (m :: * -> *). PandocMonad m => CRLParser m Pandoc
parseCreole ParserState
forall a. Default a => a
def{ stateOptions = opts } Sources
sources
case Either PandocError Pandoc
res of
Left PandocError
e -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
Right Pandoc
d -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
d
type CRLParser = ParsecT Sources ParserState
(<+>) :: (Monad m, Semigroup a) => m a -> m a -> m a
<+> :: forall (m :: * -> *) a. (Monad m, Semigroup a) => m a -> m a -> m a
(<+>) = (a -> a -> a) -> m a -> m a -> m a
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)
enclosed :: (Show end, PandocMonad m) => CRLParser m start
-> CRLParser m end
-> CRLParser m a
-> CRLParser m [a]
enclosed :: forall end (m :: * -> *) start a.
(Show end, PandocMonad m) =>
CRLParser m start
-> CRLParser m end -> CRLParser m a -> CRLParser m [a]
enclosed CRLParser m start
start CRLParser m end
end CRLParser m a
parser = ParsecT Sources ParserState m [a]
-> ParsecT Sources ParserState m [a]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [a]
-> ParsecT Sources ParserState m [a])
-> ParsecT Sources ParserState m [a]
-> ParsecT Sources ParserState m [a]
forall a b. (a -> b) -> a -> b
$ CRLParser m start
start CRLParser m start
-> ParsecT Sources ParserState m [a]
-> ParsecT Sources ParserState m [a]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CRLParser m a
-> CRLParser m end -> ParsecT Sources ParserState m [a]
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 CRLParser m a
parser CRLParser m end
end
specialChars :: [Char]
specialChars :: [Char]
specialChars = [Char]
"*/~{}\\|[]()<>\"'"
parseCreole :: PandocMonad m => CRLParser m Pandoc
parseCreole :: forall (m :: * -> *). PandocMonad m => CRLParser m Pandoc
parseCreole = do
Blocks
bs <- [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
block
ParsecT Sources ParserState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
Pandoc -> CRLParser m Pandoc
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> CRLParser m Pandoc) -> Pandoc -> CRLParser m Pandoc
forall a b. (a -> b) -> a -> b
$ Blocks -> Pandoc
B.doc Blocks
bs
block :: PandocMonad m => CRLParser m B.Blocks
block :: forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
block = do
Blocks
res <- Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT Sources ParserState m () -> CRLParser m Blocks
forall a b.
a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
CRLParser m Blocks -> CRLParser m Blocks -> CRLParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
nowiki
CRLParser m Blocks -> CRLParser m Blocks -> CRLParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
header
CRLParser m Blocks -> CRLParser m Blocks -> CRLParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
horizontalRule
CRLParser m Blocks -> CRLParser m Blocks -> CRLParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int -> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
anyList Int
1
CRLParser m Blocks -> CRLParser m Blocks -> CRLParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
table
CRLParser m Blocks -> CRLParser m Blocks -> CRLParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
para
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
Blocks -> CRLParser m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res
nowiki :: PandocMonad m => CRLParser m B.Blocks
nowiki :: forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
nowiki = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ ([Text] -> Blocks)
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m Blocks
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Blocks
B.codeBlock (Text -> Blocks) -> ([Text] -> Text) -> [Text] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat) (ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
nowikiStart
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Text]
-> ParsecT Sources ParserState m [Text]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Char
-> 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
content ParsecT Sources ParserState m Char
nowikiEnd)
where
content :: ParsecT Sources ParserState m Text
content = ParsecT Sources ParserState m Text
brackets 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
line
brackets :: ParsecT Sources ParserState m Text
brackets = 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
$ Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" (Char -> Text
T.singleton (Char -> Text)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
forall (m :: * -> *) 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 Text
-> ParsecT Sources ParserState m Text
forall (m :: * -> *) a. (Monad m, Semigroup a) => m a -> m a -> m a
<+> (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' ' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' ') ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall (m :: * -> *) a. (Monad m, Semigroup a) => m a -> m a -> m a
<+> Text -> ParsecT Sources ParserState m Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
"}}}") ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
eol)
line :: ParsecT Sources ParserState m Text
line = Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" (Char -> Text
T.singleton (Char -> Text)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
forall (m :: * -> *) 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 Text
-> ParsecT Sources ParserState m Text
forall (m :: * -> *) a. (Monad m, Semigroup a) => m a -> m a -> m a
<+> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar ParsecT Sources ParserState m Char
eol
eol :: ParsecT Sources ParserState m Char
eol = ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m 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
nowikiEnd ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
nowikiStart :: ParsecT Sources u m Char
nowikiStart = ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional 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 ()
-> ParsecT Sources u m [Char] -> ParsecT Sources u m [Char]
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Char] -> ParsecT Sources u m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"{{{" ParsecT Sources u m [Char]
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources u m ()
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
nowikiEnd :: ParsecT Sources ParserState m Char
nowikiEnd = 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
$ CRLParser m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
linebreak CRLParser m Inlines
-> 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]
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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m 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
header :: PandocMonad m => CRLParser m B.Blocks
= ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Int
level <-
([Char] -> Int)
-> ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Int
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (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
'='))
Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
6
ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
Inlines
content <- Text -> Inlines
B.str (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ([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
forall {u}. ParsecT Sources u m Char
headerEnd
Blocks -> ParsecT Sources ParserState m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources ParserState m Blocks)
-> Blocks -> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Int -> Inlines -> Blocks
B.header Int
level Inlines
content
where
headerEnd :: ParsecT Sources u m Char
headerEnd = ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Char -> ParsecT Sources u m Char)
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources u m ()
-> ParsecT Sources u m [Char] -> ParsecT Sources u m [Char]
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'=') ParsecT Sources u m [Char]
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources u m ()
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
unorderedList :: PandocMonad m => Int -> CRLParser m B.Blocks
unorderedList :: forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
unorderedList = Char -> ([Blocks] -> Blocks) -> Int -> CRLParser m Blocks
forall (m :: * -> *).
PandocMonad m =>
Char -> ([Blocks] -> Blocks) -> Int -> CRLParser m Blocks
list Char
'*' [Blocks] -> Blocks
B.bulletList
orderedList :: PandocMonad m => Int -> CRLParser m B.Blocks
orderedList :: forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
orderedList = Char -> ([Blocks] -> Blocks) -> Int -> CRLParser m Blocks
forall (m :: * -> *).
PandocMonad m =>
Char -> ([Blocks] -> Blocks) -> Int -> CRLParser m Blocks
list Char
'#' [Blocks] -> Blocks
B.orderedList
anyList :: PandocMonad m => Int -> CRLParser m B.Blocks
anyList :: forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
anyList Int
n = Int -> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
unorderedList Int
n CRLParser m Blocks -> CRLParser m Blocks -> CRLParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int -> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
orderedList Int
n
anyListItem :: PandocMonad m => Int -> CRLParser m B.Blocks
anyListItem :: forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
anyListItem Int
n = Char -> Int -> CRLParser m Blocks
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> CRLParser m Blocks
listItem Char
'*' Int
n CRLParser m Blocks -> CRLParser m Blocks -> CRLParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> Int -> CRLParser m Blocks
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> CRLParser m Blocks
listItem Char
'#' Int
n
list :: PandocMonad m => Char -> ([B.Blocks] -> B.Blocks) -> Int -> CRLParser m B.Blocks
list :: forall (m :: * -> *).
PandocMonad m =>
Char -> ([Blocks] -> Blocks) -> Int -> CRLParser m Blocks
list Char
c [Blocks] -> Blocks
f Int
n =
([Blocks] -> Blocks)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Blocks
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Blocks] -> Blocks
f (ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Blocks
itemPlusSublist ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> Int -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> CRLParser m Blocks
listItem Char
c Int
n))
where itemPlusSublist :: ParsecT Sources ParserState m Blocks
itemPlusSublist = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ Char -> Int -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> CRLParser m Blocks
listItem Char
c Int
n ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall (m :: * -> *) a. (Monad m, Semigroup a) => m a -> m a -> m a
<+> Int -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
anyList (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
listItem :: PandocMonad m => Char -> Int -> CRLParser m B.Blocks
listItem :: forall (m :: * -> *).
PandocMonad m =>
Char -> Int -> CRLParser m Blocks
listItem Char
c Int
n =
([Inlines] -> Blocks)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Blocks
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Blocks
B.plain (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
B.trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat) (ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
listStart 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
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
inline ParsecT Sources ParserState m ()
itemEnd)
where
listStart :: ParsecT Sources u m ()
listStart = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional 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 ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
ParsecT Sources u m ()
-> ParsecT Sources u m [Char] -> ParsecT Sources u m [Char]
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ParsecT Sources u m Char -> ParsecT Sources u 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
n (Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c)
ParsecT Sources u m [Char]
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ([Char] -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char
c]) ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
itemEnd :: ParsecT Sources ParserState m ()
itemEnd = ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => CRLParser m ()
endOfParaElement ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int -> ParsecT Sources ParserState m ()
forall {m :: * -> *} {a}.
(PandocMonad m, Monoid a) =>
Int -> ParsecT Sources ParserState m a
nextItem Int
n
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
3 then Int -> ParsecT Sources ParserState m ()
forall {m :: * -> *} {a}.
(PandocMonad m, Monoid a) =>
Int -> ParsecT Sources ParserState m a
nextItem (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
else Int -> ParsecT Sources ParserState m ()
forall {m :: * -> *} {a}.
(PandocMonad m, Monoid a) =>
Int -> ParsecT Sources ParserState m a
nextItem (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int -> ParsecT Sources ParserState m ()
forall {m :: * -> *} {a}.
(PandocMonad m, Monoid a) =>
Int -> ParsecT Sources ParserState m a
nextItem (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
nextItem :: Int -> ParsecT Sources ParserState m a
nextItem Int
x = ParsecT Sources ParserState m a -> ParsecT Sources ParserState m a
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 a
-> ParsecT Sources ParserState m a)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m a
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m a -> ParsecT Sources ParserState m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m a)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m a
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
anyListItem Int
x ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m a
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> a -> ParsecT Sources ParserState m a
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty
table :: PandocMonad m => CRLParser m B.Blocks
table :: forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
table = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ do
Maybe [Blocks]
headers <- ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m (Maybe [Blocks])
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe ParsecT Sources ParserState m [Blocks]
headerRow
[[Blocks]]
rows <- ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [[Blocks]]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m [Blocks]
row
Blocks -> ParsecT Sources ParserState m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT Sources ParserState m Blocks)
-> Blocks -> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [[Blocks]] -> Blocks
B.simpleTable ([Blocks] -> Maybe [Blocks] -> [Blocks]
forall a. a -> Maybe a -> a
fromMaybe [Blocks
forall a. Monoid a => a
mempty] Maybe [Blocks]
headers) [[Blocks]]
rows
where
headerRow :: ParsecT Sources ParserState m [Blocks]
headerRow = ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [Blocks])
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [Blocks]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [Blocks]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Blocks]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m Blocks
headerCell ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
rowEnd
headerCell :: ParsecT Sources ParserState m Blocks
headerCell = Inlines -> Blocks
B.plain (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
B.trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat
([Inlines] -> Blocks)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([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 [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 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 => CRLParser m Inlines
inline ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
cellEnd)
row :: ParsecT Sources ParserState m [Blocks]
row = ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [Blocks])
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [Blocks]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m [Blocks]
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Blocks]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m Blocks
cell ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
rowEnd
cell :: ParsecT Sources ParserState m Blocks
cell = Inlines -> Blocks
B.plain (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
B.trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat
([Inlines] -> Blocks)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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 Char
-> ParsecT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
inline ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
cellEnd)
rowEnd :: ParsecT Sources u m Char
rowEnd = ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Char -> ParsecT Sources u m Char)
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|') ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources u m ()
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
cellEnd :: ParsecT Sources u m Char
cellEnd = 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 -> ParsecT Sources u m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Char -> ParsecT Sources u m Char)
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' 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 {u}. ParsecT Sources u m Char
rowEnd
para :: PandocMonad m => CRLParser m B.Blocks
para :: forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
para = ([Inlines] -> Blocks)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Blocks
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Blocks
result (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat) (ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParsecT s st m a -> ParsecT s st m end -> ParsecT s st m [a]
many1Till ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
inline ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => CRLParser m ()
endOfParaElement)
where
result :: Inlines -> Blocks
result Inlines
content = if (Inline -> Bool) -> Inlines -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all (Inline -> Inline -> Bool
forall a. Eq a => a -> a -> Bool
==Inline
Space) Inlines
content
then Blocks
forall a. Monoid a => a
mempty
else Inlines -> Blocks
B.para (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.trimInlines Inlines
content
endOfParaElement :: PandocMonad m => CRLParser m ()
endOfParaElement :: forall (m :: * -> *). PandocMonad m => CRLParser m ()
endOfParaElement = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
endOfInput ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
forall {u}. ParsecT Sources u m ()
endOfPara
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
startOfList ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
startOfTable
ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
startOfHeader ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
hr ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
startOfNowiki
where
endOfInput :: ParsecT Sources u m ()
endOfInput = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
endOfPara :: ParsecT Sources u m ()
endOfPara = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline
startOf :: PandocMonad m => CRLParser m a -> CRLParser m ()
startOf :: forall (m :: * -> *) a.
PandocMonad m =>
CRLParser m a -> CRLParser m ()
startOf CRLParser m a
p = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources ParserState m Char
-> CRLParser m a -> CRLParser m a
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CRLParser m a
p CRLParser m a
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT Sources ParserState m ()
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
forall a. Monoid a => a
mempty
startOfList :: ParsecT Sources ParserState m ()
startOfList = CRLParser m Blocks -> ParsecT Sources ParserState m ()
forall (m :: * -> *) a.
PandocMonad m =>
CRLParser m a -> CRLParser m ()
startOf (CRLParser m Blocks -> ParsecT Sources ParserState m ())
-> CRLParser m Blocks -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Int -> CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => Int -> CRLParser m Blocks
anyListItem Int
1
startOfTable :: ParsecT Sources ParserState m ()
startOfTable = CRLParser m Blocks -> ParsecT Sources ParserState m ()
forall (m :: * -> *) a.
PandocMonad m =>
CRLParser m a -> CRLParser m ()
startOf CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
table
startOfHeader :: ParsecT Sources ParserState m ()
startOfHeader = CRLParser m Blocks -> ParsecT Sources ParserState m ()
forall (m :: * -> *) a.
PandocMonad m =>
CRLParser m a -> CRLParser m ()
startOf CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
header
startOfNowiki :: ParsecT Sources ParserState m ()
startOfNowiki = CRLParser m Blocks -> ParsecT Sources ParserState m ()
forall (m :: * -> *) a.
PandocMonad m =>
CRLParser m a -> CRLParser m ()
startOf CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
nowiki
hr :: ParsecT Sources ParserState m ()
hr = CRLParser m Blocks -> ParsecT Sources ParserState m ()
forall (m :: * -> *) a.
PandocMonad m =>
CRLParser m a -> CRLParser m ()
startOf CRLParser m Blocks
forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
horizontalRule
horizontalRule :: PandocMonad m => CRLParser m B.Blocks
horizontalRule :: forall (m :: * -> *). PandocMonad m => CRLParser m Blocks
horizontalRule = ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks)
-> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m Blocks
forall a b. (a -> b) -> a -> b
$ 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]
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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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 Blocks
-> ParsecT Sources ParserState m Blocks
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> ParsecT Sources ParserState m Blocks
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
B.horizontalRule
inline :: PandocMonad m => CRLParser m B.Inlines
inline :: forall (m :: * -> *). PandocMonad m => CRLParser 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 => CRLParser m Inlines
whitespace
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
escapedLink
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
escapedChar
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
link
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
inlineNowiki
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
placeholder
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
image
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
forcedLinebreak
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
bold
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
finalBold
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
italics
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
finalItalics
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
str
, ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
symbol
] 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"
escapedChar :: PandocMonad m => CRLParser m B.Inlines
escapedChar :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
escapedChar =
(Char -> Inlines)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Inlines
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Inlines
B.str (Text -> Inlines) -> (Char -> Text) -> Char -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton) (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'~' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Char] -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"\t\n ")
escapedLink :: PandocMonad m => CRLParser m B.Inlines
escapedLink :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
escapedLink = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ do
Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'~'
(Text
orig, Text
_) <- ParsecT Sources ParserState m (Text, Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (Text, Text)
uri
Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT Sources ParserState m Inlines)
-> Inlines -> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
orig
image :: PandocMonad m => CRLParser m B.Inlines
image :: forall (m :: * -> *). PandocMonad m => CRLParser 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
(Text
orig, Text
src) <- ParsecT Sources ParserState m (Text, Text)
forall {u}. ParsecT Sources u m (Text, Text)
wikiImg
Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT Sources ParserState m Inlines)
-> Inlines -> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.image Text
src Text
"" (Text -> Inlines
B.str Text
orig)
where
linkSrc :: ParsecT Sources st m Text
linkSrc = ParsecT Sources st m Char -> ParsecT Sources st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar (ParsecT Sources st m Char -> ParsecT Sources st m Text)
-> ParsecT Sources st m Char -> ParsecT Sources st m Text
forall a b. (a -> b) -> a -> b
$ [Char] -> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"|}\n\r\t"
linkDsc :: ParsecT Sources u m Text
linkDsc = Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' ParsecT Sources u m Char
-> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> ParsecT Sources u m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar ([Char] -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"}\n\r\t")
wikiImg :: ParsecT Sources u m (Text, Text)
wikiImg = ParsecT Sources u m (Text, Text)
-> ParsecT Sources u m (Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m (Text, Text)
-> ParsecT Sources u m (Text, Text))
-> ParsecT Sources u m (Text, Text)
-> ParsecT Sources u m (Text, Text)
forall a b. (a -> b) -> a -> b
$ do
[Char] -> ParsecT Sources u m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"{{"
Text
src <- ParsecT Sources u m Text
forall {st}. ParsecT Sources st m Text
linkSrc
Text
dsc <- Text -> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" ParsecT Sources u m Text
forall {st}. ParsecT Sources st m Text
linkDsc
[Char] -> ParsecT Sources u m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"}}"
(Text, Text) -> ParsecT Sources u m (Text, Text)
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
dsc, Text
src)
link :: PandocMonad m => CRLParser m B.Inlines
link :: forall (m :: * -> *). PandocMonad m => CRLParser 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
(Inlines
orig, Text
src) <- ParsecT Sources ParserState m (Inlines, Text)
forall {u}. ParsecT Sources u m (Inlines, Text)
uriLink ParsecT Sources ParserState m (Inlines, Text)
-> ParsecT Sources ParserState m (Inlines, Text)
-> ParsecT Sources ParserState m (Inlines, Text)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m (Inlines, Text)
wikiLink
Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT Sources ParserState m Inlines)
-> Inlines -> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link Text
src Text
"" Inlines
orig
where
linkSrc :: ParsecT Sources st m Text
linkSrc = ParsecT Sources st m Char -> ParsecT Sources st m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar (ParsecT Sources st m Char -> ParsecT Sources st m Text)
-> ParsecT Sources st m Char -> ParsecT Sources st m Text
forall a b. (a -> b) -> a -> b
$ [Char] -> ParsecT Sources st m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"|]\n\r\t"
linkDsc :: PandocMonad m => Text -> CRLParser m B.Inlines
linkDsc :: forall (m :: * -> *). PandocMonad m => Text -> CRLParser m Inlines
linkDsc Text
otxt = Text -> Inlines
B.str
(Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
otxt
(Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar ([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\r\t")))
linkImg :: ParsecT Sources ParserState m Inlines
linkImg = 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
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
image
wikiLink :: ParsecT Sources ParserState m (Inlines, Text)
wikiLink = ParsecT Sources ParserState m (Inlines, Text)
-> ParsecT Sources ParserState m (Inlines, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m (Inlines, Text)
-> ParsecT Sources ParserState m (Inlines, Text))
-> ParsecT Sources ParserState m (Inlines, Text)
-> ParsecT Sources ParserState m (Inlines, Text)
forall a b. (a -> b) -> a -> b
$ do
[Char] -> ParsecT Sources ParserState m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"[["
Text
src <- ParsecT Sources ParserState m Text
forall {st}. ParsecT Sources st m Text
linkSrc
Inlines
dsc <- ParsecT Sources ParserState m Inlines
linkImg ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => Text -> CRLParser m Inlines
linkDsc Text
src
[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]
"]]"
(Inlines, Text) -> ParsecT Sources ParserState m (Inlines, Text)
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
dsc, Text
src)
uriLink :: ParsecT Sources u m (Inlines, Text)
uriLink = ParsecT Sources u m (Inlines, Text)
-> ParsecT Sources u m (Inlines, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m (Inlines, Text)
-> ParsecT Sources u m (Inlines, Text))
-> ParsecT Sources u m (Inlines, Text)
-> ParsecT Sources u m (Inlines, Text)
forall a b. (a -> b) -> a -> b
$ do
(Text
orig, Text
src) <- ParsecT Sources u m (Text, Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (Text, Text)
uri
(Inlines, Text) -> ParsecT Sources u m (Inlines, Text)
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
B.str Text
orig, Text
src)
inlineNowiki :: PandocMonad m => CRLParser m B.Inlines
inlineNowiki :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
inlineNowiki = Text -> Inlines
B.code (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT Sources ParserState m [Char]
forall {u}. ParsecT Sources u m [Char]
start ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st a.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m a -> ParsecT s st m Text
manyTillChar ([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\r") ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
end)
where
start :: ParsecT Sources u m [Char]
start = ParsecT Sources u m [Char] -> ParsecT Sources u m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m [Char] -> ParsecT Sources u m [Char])
-> ParsecT Sources u m [Char] -> ParsecT Sources u m [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> ParsecT Sources u m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"{{{"
end :: ParsecT Sources u m Char
end = ParsecT Sources u m Char -> ParsecT Sources u m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Char -> ParsecT Sources u m Char)
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b. (a -> b) -> a -> b
$ [Char] -> ParsecT Sources u m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"}}}" ParsecT Sources u m [Char]
-> ParsecT Sources u m Char -> ParsecT Sources u m Char
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Char -> 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 ([Char] -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
"}")
placeholder :: PandocMonad m => CRLParser m B.Inlines
placeholder :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
placeholder = Text -> Inlines
B.text (Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 ([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
-> 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]
string [Char]
">>>")
ParsecT Sources ParserState m [Char]
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> ParsecT Sources ParserState m Text
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"")
whitespace :: PandocMonad m => CRLParser m B.Inlines
whitespace :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
whitespace = ParsecT Sources ParserState m Inlines
lb ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
forall {u}. ParsecT Sources u m Inlines
regsp
where lb :: ParsecT Sources ParserState m Inlines
lb = ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
linebreak ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
regsp :: ParsecT Sources u m Inlines
regsp = ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines)
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources u m ()
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
linebreak :: PandocMonad m => CRLParser m B.Inlines
linebreak :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
linebreak = ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (ParsecT Sources ParserState m Inlines
forall {u}. ParsecT Sources u m Inlines
lastNewline ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
innerNewline)
where lastNewline :: ParsecT Sources u m Inlines
lastNewline = ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources u m ()
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b.
ParsecT Sources u m a
-> ParsecT Sources u m b -> ParsecT Sources u m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall a. a -> ParsecT Sources u m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
innerNewline :: ParsecT Sources ParserState m Inlines
innerNewline = Inlines -> ParsecT Sources ParserState m Inlines
forall a. a -> ParsecT Sources ParserState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
symbol :: PandocMonad m => CRLParser m B.Inlines
symbol :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
symbol = (Char -> Inlines)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Inlines
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Inlines
B.str (Text -> Inlines) -> (Char -> Text) -> Char -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton) ([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]
specialChars)
str :: PandocMonad m => CRLParser m B.Inlines
str :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
str = let strChar :: ParsecT Sources u m Char
strChar = [Char] -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf ([Char]
"\t\n " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
specialChars) in
(Text -> Inlines)
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Inlines
forall a b.
(a -> b)
-> ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Inlines
B.str (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources ParserState m Char
forall {u}. ParsecT Sources u m Char
strChar)
bold :: PandocMonad m => CRLParser m B.Inlines
bold :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
bold = Inlines -> Inlines
B.strong (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
CRLParser m [Char]
-> CRLParser m [Char]
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Inlines]
forall end (m :: * -> *) start a.
(Show end, PandocMonad m) =>
CRLParser m start
-> CRLParser m end -> CRLParser m a -> CRLParser m [a]
enclosed ([Char] -> CRLParser m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"**") (CRLParser m [Char] -> CRLParser m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (CRLParser m [Char] -> CRLParser m [Char])
-> CRLParser m [Char] -> CRLParser m [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> CRLParser 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 Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
inline
italics :: PandocMonad m => CRLParser m B.Inlines
italics :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
italics = Inlines -> Inlines
B.emph (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
CRLParser m [Char]
-> CRLParser m [Char]
-> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m [Inlines]
forall end (m :: * -> *) start a.
(Show end, PandocMonad m) =>
CRLParser m start
-> CRLParser m end -> CRLParser m a -> CRLParser m [a]
enclosed ([Char] -> CRLParser m [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"//") (CRLParser m [Char] -> CRLParser m [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (CRLParser m [Char] -> CRLParser m [Char])
-> CRLParser m [Char] -> CRLParser m [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> CRLParser 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 Inlines
forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
inline
finalBold :: PandocMonad m => CRLParser m B.Inlines
finalBold :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
finalBold = Inlines -> Inlines
B.strong (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
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 ([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 [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 ()
-> 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 => CRLParser m Inlines
inline ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => CRLParser m ()
endOfParaElement)
finalItalics :: PandocMonad m => CRLParser m B.Inlines
finalItalics :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
finalItalics = Inlines -> Inlines
B.emph (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
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 ([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 [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 ()
-> 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 => CRLParser m Inlines
inline ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => CRLParser m ()
endOfParaElement)
forcedLinebreak :: PandocMonad m => CRLParser m B.Inlines
forcedLinebreak :: forall (m :: * -> *). PandocMonad m => CRLParser m Inlines
forcedLinebreak = 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]
string [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
>> 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