{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.Org.Inlines
( inline
, inlines
, addToNotesTable
, linkTarget
) where
import Text.Pandoc.Readers.Org.BlockStarts (endOfBlock, noteMarker)
import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
import Text.Pandoc.Readers.Org.Shared (cleanLinkText, isImageFilename,
originalLang, translateLang, exportsCode)
import Text.Pandoc.Builder (Inlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Options
import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)
import Text.TeXMath (DisplayType (..), readTeX, writePandoc)
import Text.Pandoc.Sources (ToSources(..))
import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
import Safe (lastMay)
import Control.Monad (guard, mplus, mzero, unless, when, void)
import Control.Monad.Trans (lift)
import Data.Char (isAlphaNum, isSpace)
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
pushToInlineCharStack :: PandocMonad m => Char -> OrgParser m ()
pushToInlineCharStack :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m ()
pushToInlineCharStack Char
c = (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s ->
OrgParserState
s{ orgStateEmphasisCharStack = c:orgStateEmphasisCharStack s }
popInlineCharStack :: PandocMonad m => OrgParser m ()
popInlineCharStack :: forall (m :: * -> *). PandocMonad m => OrgParser m ()
popInlineCharStack = (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s ->
OrgParserState
s{ orgStateEmphasisCharStack = drop 1 . orgStateEmphasisCharStack $ s }
surroundingEmphasisChar :: PandocMonad m => OrgParser m [Char]
surroundingEmphasisChar :: forall (m :: * -> *). PandocMonad m => OrgParser m [Char]
surroundingEmphasisChar =
Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
take Int
1 ([Char] -> [Char])
-> (OrgParserState -> [Char]) -> OrgParserState -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Char] -> [Char]
forall a. Int -> [a] -> [a]
drop Int
1 ([Char] -> [Char])
-> (OrgParserState -> [Char]) -> OrgParserState -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> [Char]
orgStateEmphasisCharStack (OrgParserState -> [Char])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
startEmphasisNewlinesCounting :: PandocMonad m => Int -> OrgParser m ()
startEmphasisNewlinesCounting :: forall (m :: * -> *). PandocMonad m => Int -> OrgParser m ()
startEmphasisNewlinesCounting Int
maxNewlines = (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s ->
OrgParserState
s{ orgStateEmphasisNewlines = Just maxNewlines }
decEmphasisNewlinesCount :: PandocMonad m => OrgParser m ()
decEmphasisNewlinesCount :: forall (m :: * -> *). PandocMonad m => OrgParser m ()
decEmphasisNewlinesCount = (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s ->
OrgParserState
s{ orgStateEmphasisNewlines = (\Int
n -> Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) <$> orgStateEmphasisNewlines s }
newlinesCountWithinLimits :: PandocMonad m => OrgParser m Bool
newlinesCountWithinLimits :: forall (m :: * -> *). PandocMonad m => OrgParser m Bool
newlinesCountWithinLimits = do
OrgParserState
st <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> OrgParser m Bool
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> OrgParser m Bool) -> Bool -> OrgParser m Bool
forall a b. (a -> b) -> a -> b
$ ((Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) (Int -> Bool) -> Maybe Int -> Maybe Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParserState -> Maybe Int
orgStateEmphasisNewlines OrgParserState
st) Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
/= Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
resetEmphasisNewlines :: PandocMonad m => OrgParser m ()
resetEmphasisNewlines :: forall (m :: * -> *). PandocMonad m => OrgParser m ()
resetEmphasisNewlines = (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s ->
OrgParserState
s{ orgStateEmphasisNewlines = Nothing }
addToNotesTable :: PandocMonad m => OrgNoteRecord -> OrgParser m ()
addToNotesTable :: forall (m :: * -> *).
PandocMonad m =>
OrgNoteRecord -> OrgParser m ()
addToNotesTable OrgNoteRecord
note = do
OrgNoteTable
oldnotes <- OrgParserState -> OrgNoteTable
orgStateNotes' (OrgParserState -> OrgNoteTable)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgNoteTable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(OrgParserState -> OrgParserState) -> OrgParser m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState) -> OrgParser m ())
-> (OrgParserState -> OrgParserState) -> OrgParser m ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s -> OrgParserState
s{ orgStateNotes' = note:oldnotes }
inline :: PandocMonad m => OrgParser m (F Inlines)
inline :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline =
[ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
whitespace
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
linebreak
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
cite
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
footnote
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
linkOrImage
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
anchor
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlineCodeBlock
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
str
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
endline
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
emphasizedText
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
code
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
math
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
displayMath
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
verbatim
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
subscript
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
superscript
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlineLaTeX
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
exportSnippet
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
macro
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
smart
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
symbol
] ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *). PandocMonad m => OrgParser m Bool
newlinesCountWithinLimits)
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> [Char] -> ParsecT s u m a
<?> [Char]
"inline"
inlines :: PandocMonad m => OrgParser m (F Inlines)
inlines :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlines = F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline
specialChars :: [Char]
specialChars :: [Char]
specialChars = [Char]
"\"$'()*+-,./:;<=>@[\\]^_{|}~"
whitespace :: PandocMonad m => OrgParser m (F Inlines)
whitespace :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
whitespace = Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
B.space F Inlines
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastPreCharPos
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastForbiddenCharPos
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> [Char] -> ParsecT s u m a
<?> [Char]
"whitespace"
linebreak :: PandocMonad m => OrgParser m (F Inlines)
linebreak :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
linebreak = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
B.linebreak F Inlines
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
str :: PandocMonad m => OrgParser m (F Inlines)
str :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
str = Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.str (Text -> F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
( ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ [Char]
specialChars [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"\n\r ") ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> (Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall {m :: * -> *}.
PandocMonad m =>
Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
updatePositions' )
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos
where
updatePositions' :: Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
updatePositions' Text
str' = Text
str' Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ((Text, Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> Maybe (Text, Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> ((Text, Char) -> Char)
-> (Text, Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, Char) -> Char
forall a b. (a, b) -> b
snd) (Text -> Maybe (Text, Char)
T.unsnoc Text
str')
endline :: PandocMonad m => OrgParser m (F Inlines)
endline :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
endline = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
endOfBlock
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
decEmphasisNewlinesCount
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *). PandocMonad m => OrgParser m Bool
newlinesCountWithinLimits
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastPreCharPos
Bool
useHardBreaks <- ExportSettings -> Bool
exportPreserveBreaks (ExportSettings -> Bool)
-> (OrgParserState -> ExportSettings) -> OrgParserState -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> ExportSettings
orgStateExportSettings (OrgParserState -> Bool)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (if Bool
useHardBreaks then Inlines
B.linebreak else Inlines
B.softbreak)
orgCite :: PandocMonad m => OrgParser m (F [Citation])
orgCite :: forall (m :: * -> *). PandocMonad m => OrgParser m (F [Citation])
orgCite = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation]))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall a b. (a -> b) -> a -> b
$ do
[Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"[cite"
(CiteStyle
sty, [CiteVariant]
_variants) <- OrgParser m (CiteStyle, [CiteVariant])
forall (m :: * -> *).
PandocMonad m =>
OrgParser m (CiteStyle, [CiteVariant])
citeStyle
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':'
OrgParser m ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
spnl
F Inlines
globalPref <- F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option F Inlines
forall a. Monoid a => a
mempty (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
citePrefix ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
';'))
F [Citation]
items <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall (m :: * -> *). PandocMonad m => OrgParser m (F [Citation])
citeItems
F Inlines
globalSuff <- F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option F Inlines
forall a. Monoid a => a
mempty (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
citeSuffix))
OrgParser m ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
spnl
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']'
F [Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F [Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation]))
-> F [Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall a b. (a -> b) -> a -> b
$ CiteStyle -> F [Citation] -> F [Citation]
adjustCiteStyle CiteStyle
sty (F [Citation] -> F [Citation])
-> (F [Citation] -> F [Citation]) -> F [Citation] -> F [Citation]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
F Inlines -> F [Citation] -> F [Citation]
addPrefixToFirstItem F Inlines
globalPref (F [Citation] -> F [Citation])
-> (F [Citation] -> F [Citation]) -> F [Citation] -> F [Citation]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
F Inlines -> F [Citation] -> F [Citation]
addSuffixToLastItem F Inlines
globalSuff (F [Citation] -> F [Citation]) -> F [Citation] -> F [Citation]
forall a b. (a -> b) -> a -> b
$ F [Citation]
items
adjustCiteStyle :: CiteStyle -> (F [Citation]) -> (F [Citation])
adjustCiteStyle :: CiteStyle -> F [Citation] -> F [Citation]
adjustCiteStyle CiteStyle
sty F [Citation]
cs = do
[Citation]
cs' <- F [Citation]
cs
case [Citation]
cs' of
[] -> [Citation] -> F [Citation]
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return []
(Citation
d:[Citation]
ds)
-> case CiteStyle
sty of
CiteStyle
TextStyle -> [Citation] -> F [Citation]
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Citation] -> F [Citation]) -> [Citation] -> F [Citation]
forall a b. (a -> b) -> a -> b
$ Citation
d{ citationMode = AuthorInText
, citationSuffix = dropWhile (== Space)
(citationSuffix d)} Citation -> [Citation] -> [Citation]
forall a. a -> [a] -> [a]
: [Citation]
ds
CiteStyle
NoAuthorStyle -> [Citation] -> F [Citation]
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Citation] -> F [Citation]) -> [Citation] -> F [Citation]
forall a b. (a -> b) -> a -> b
$ Citation
d{ citationMode = SuppressAuthor } Citation -> [Citation] -> [Citation]
forall a. a -> [a] -> [a]
: [Citation]
ds
CiteStyle
_ -> [Citation] -> F [Citation]
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Citation
dCitation -> [Citation] -> [Citation]
forall a. a -> [a] -> [a]
:[Citation]
ds)
addPrefixToFirstItem :: (F Inlines) -> (F [Citation]) -> (F [Citation])
addPrefixToFirstItem :: F Inlines -> F [Citation] -> F [Citation]
addPrefixToFirstItem F Inlines
aff F [Citation]
cs = do
[Citation]
cs' <- F [Citation]
cs
Inlines
aff' <- F Inlines
aff
case [Citation]
cs' of
[] -> [Citation] -> F [Citation]
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return []
(Citation
d:[Citation]
ds) -> [Citation] -> F [Citation]
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Citation
d{ citationPrefix =
B.toList aff' <> citationPrefix d }Citation -> [Citation] -> [Citation]
forall a. a -> [a] -> [a]
:[Citation]
ds)
addSuffixToLastItem :: (F Inlines) -> (F [Citation]) -> (F [Citation])
addSuffixToLastItem :: F Inlines -> F [Citation] -> F [Citation]
addSuffixToLastItem F Inlines
aff F [Citation]
cs = do
[Citation]
cs' <- F [Citation]
cs
Inlines
aff' <- F Inlines
aff
case [Citation] -> Maybe Citation
forall a. [a] -> Maybe a
lastMay [Citation]
cs' of
Maybe Citation
Nothing -> [Citation] -> F [Citation]
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return [Citation]
cs'
Just Citation
d ->
[Citation] -> F [Citation]
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Citation] -> [Citation]
forall a. HasCallStack => [a] -> [a]
init [Citation]
cs' [Citation] -> [Citation] -> [Citation]
forall a. [a] -> [a] -> [a]
++ [Citation
d{ citationSuffix =
citationSuffix d <> B.toList aff' }])
citeItems :: PandocMonad m => OrgParser m (F [Citation])
citeItems :: forall (m :: * -> *). PandocMonad m => OrgParser m (F [Citation])
citeItems = [Future OrgParserState Citation] -> F [Citation]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([Future OrgParserState Citation] -> F [Citation])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
[Future OrgParserState Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m (Future OrgParserState Citation)
forall (m :: * -> *).
PandocMonad m =>
OrgParser m (Future OrgParserState Citation)
citeItem OrgParser m (Future OrgParserState Citation)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
[Future OrgParserState Citation]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
`sepBy1` (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
';')
citeItem :: PandocMonad m => OrgParser m (F Citation)
citeItem :: forall (m :: * -> *).
PandocMonad m =>
OrgParser m (Future OrgParserState Citation)
citeItem = do
F Inlines
pref <- OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
citePrefix
Text
itemKey <- OrgParser m Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
orgCiteKey
F Inlines
suff <- OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
citeSuffix
Future OrgParserState Citation
-> OrgParser m (Future OrgParserState Citation)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future OrgParserState Citation
-> OrgParser m (Future OrgParserState Citation))
-> Future OrgParserState Citation
-> OrgParser m (Future OrgParserState Citation)
forall a b. (a -> b) -> a -> b
$ do
Inlines
pre' <- F Inlines
pref
Inlines
suf' <- F Inlines
suff
Citation -> Future OrgParserState Citation
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Citation
{ citationId :: Text
citationId = Text
itemKey
, citationPrefix :: [Inline]
citationPrefix = Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
pre'
, citationSuffix :: [Inline]
citationSuffix = Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
suf'
, citationMode :: CitationMode
citationMode = CitationMode
NormalCitation
, citationNoteNum :: Int
citationNoteNum = Int
0
, citationHash :: Int
citationHash = Int
0
}
orgCiteKey :: PandocMonad m => OrgParser m Text
orgCiteKey :: forall (m :: * -> *). PandocMonad m => OrgParser m Text
orgCiteKey = do
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'@'
[Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> OrgParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
orgCiteKeyChar)
orgCiteKeyChar :: Char -> Bool
orgCiteKeyChar :: Char -> Bool
orgCiteKeyChar Char
c =
Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'.',Char
':',Char
'?',Char
'!',Char
'`',Char
'\'',Char
'/',Char
'*',Char
'@',Char
'+',Char
'|',
Char
'(',Char
')',Char
'{',Char
'}',Char
'<',Char
'>',Char
'&',Char
'_',Char
'^',Char
'$',Char
'#',
Char
'%',Char
'~',Char
'-']
rawAffix :: PandocMonad m => Bool -> OrgParser m Text
rawAffix :: forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m Text
rawAffix Bool
isPrefix = ([()], Text) -> Text
forall a b. (a, b) -> b
snd (([()], Text) -> Text)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ([()], Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [()]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) ([()], Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw
(ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [()]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many
(ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall {u}. ParsecT Sources u (ReaderT OrgParserLocal m) ()
affixChar
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m Text
rawAffix Bool
isPrefix ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']'))))
where
affixChar :: ParsecT Sources u (ReaderT OrgParserLocal m) ()
affixChar = ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) ())
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy ((Char -> Bool)
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char)
-> (Char -> Bool)
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ \Char
c ->
Bool -> Bool
not (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'^' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
';' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'[' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
']') Bool -> Bool -> Bool
&&
(Bool -> Bool
not Bool
isPrefix Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'@')
citePrefix :: PandocMonad m => OrgParser m (F Inlines)
citePrefix :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
citePrefix =
Bool -> OrgParser m Text
forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m Text
rawAffix Bool
True OrgParser m Text
-> (Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString (F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline)
citeSuffix :: PandocMonad m => OrgParser m (F Inlines)
citeSuffix :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
citeSuffix =
Bool -> OrgParser m Text
forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m Text
rawAffix Bool
False OrgParser m Text
-> (Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
parseSuffix
where
parseSuffix :: ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
parseSuffix = do
Bool
hasSpace <- Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
nonspaceChar))
F Inlines
ils <- F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ if Bool
hasSpace
then (Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>) (Inlines -> Inlines) -> F Inlines -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F Inlines
ils
else F Inlines
ils
citeStyle :: PandocMonad m => OrgParser m (CiteStyle, [CiteVariant])
citeStyle :: forall (m :: * -> *).
PandocMonad m =>
OrgParser m (CiteStyle, [CiteVariant])
citeStyle = (CiteStyle, [CiteVariant])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(CiteStyle, [CiteVariant])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(CiteStyle, [CiteVariant])
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (CiteStyle
DefStyle, []) (ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(CiteStyle, [CiteVariant])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(CiteStyle, [CiteVariant]))
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(CiteStyle, [CiteVariant])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(CiteStyle, [CiteVariant])
forall a b. (a -> b) -> a -> b
$ do
CiteStyle
sty <- CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option CiteStyle
DefStyle (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b. (a -> b) -> a -> b
$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b. (a -> b) -> a -> b
$ Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall (m :: * -> *). PandocMonad m => OrgParser m CiteStyle
orgCiteStyle
[CiteVariant]
variants <- [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall a b. (a -> b) -> a -> b
$ ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall a b. (a -> b) -> a -> b
$ Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall (m :: * -> *). PandocMonad m => OrgParser m [CiteVariant]
orgCiteVariants
(CiteStyle, [CiteVariant])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(CiteStyle, [CiteVariant])
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (CiteStyle
sty, [CiteVariant]
variants)
orgCiteStyle :: PandocMonad m => OrgParser m CiteStyle
orgCiteStyle :: forall (m :: * -> *). PandocMonad m => OrgParser m CiteStyle
orgCiteStyle = [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ([ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle)
-> [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b. (a -> b) -> a -> b
$ (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle)
-> [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle]
-> [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle]
forall a b. (a -> b) -> [a] -> [b]
map ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try
[ CiteStyle
NoAuthorStyle CiteStyle
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"noauthor"
, CiteStyle
NoAuthorStyle CiteStyle
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"na"
, CiteStyle
LocatorsStyle CiteStyle
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"locators"
, CiteStyle
LocatorsStyle CiteStyle
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'l'
, CiteStyle
NociteStyle CiteStyle
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"nocite"
, CiteStyle
NociteStyle CiteStyle
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'n'
, CiteStyle
TextStyle CiteStyle
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"text"
, CiteStyle
TextStyle CiteStyle
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteStyle
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
't'
]
orgCiteVariants :: PandocMonad m => OrgParser m [CiteVariant]
orgCiteVariants :: forall (m :: * -> *). PandocMonad m => OrgParser m [CiteVariant]
orgCiteVariants =
(ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteVariant
forall {u}.
ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
fullnameVariant ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteVariant
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
`sepBy1` (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteVariant
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [CiteVariant]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CiteVariant
forall {u}.
ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
onecharVariant)
where
fullnameVariant :: ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
fullnameVariant = [ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant]
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ([ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant]
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant)
-> [ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant]
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall a b. (a -> b) -> a -> b
$ (ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant)
-> [ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant]
-> [ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant]
forall a b. (a -> b) -> [a] -> [b]
map ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try
[ CiteVariant
Bare CiteVariant
-> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall a b.
a
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
-> ParsecT Sources u (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char] -> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"bare"
, CiteVariant
Caps CiteVariant
-> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall a b.
a
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
-> ParsecT Sources u (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char] -> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"caps"
, CiteVariant
Full CiteVariant
-> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall a b.
a
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
-> ParsecT Sources u (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char] -> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"full"
]
onecharVariant :: ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
onecharVariant = [ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant]
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ CiteVariant
Bare CiteVariant
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall a b.
a
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
-> ParsecT Sources u (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'b'
, CiteVariant
Caps CiteVariant
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall a b.
a
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
-> ParsecT Sources u (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'c'
, CiteVariant
Full CiteVariant
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) CiteVariant
forall a b.
a
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
-> ParsecT Sources u (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'f'
]
data CiteStyle =
NoAuthorStyle
|
| NociteStyle
| TextStyle
| DefStyle
deriving Int -> CiteStyle -> [Char] -> [Char]
[CiteStyle] -> [Char] -> [Char]
CiteStyle -> [Char]
(Int -> CiteStyle -> [Char] -> [Char])
-> (CiteStyle -> [Char])
-> ([CiteStyle] -> [Char] -> [Char])
-> Show CiteStyle
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> CiteStyle -> [Char] -> [Char]
showsPrec :: Int -> CiteStyle -> [Char] -> [Char]
$cshow :: CiteStyle -> [Char]
show :: CiteStyle -> [Char]
$cshowList :: [CiteStyle] -> [Char] -> [Char]
showList :: [CiteStyle] -> [Char] -> [Char]
Show
data CiteVariant =
Caps
| Bare
| Full
deriving Int -> CiteVariant -> [Char] -> [Char]
[CiteVariant] -> [Char] -> [Char]
CiteVariant -> [Char]
(Int -> CiteVariant -> [Char] -> [Char])
-> (CiteVariant -> [Char])
-> ([CiteVariant] -> [Char] -> [Char])
-> Show CiteVariant
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> CiteVariant -> [Char] -> [Char]
showsPrec :: Int -> CiteVariant -> [Char] -> [Char]
$cshow :: CiteVariant -> [Char]
show :: CiteVariant -> [Char]
$cshowList :: [CiteVariant] -> [Char] -> [Char]
showList :: [CiteVariant] -> [Char] -> [Char]
Show
spnl :: PandocMonad m => OrgParser m ()
spnl :: forall (m :: * -> *). PandocMonad m => OrgParser m ()
spnl =
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline OrgParser m Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy OrgParser m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
blankline ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces)
cite :: PandocMonad m => OrgParser m (F Inlines)
cite :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
cite = do
Extension
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_citations
(F [Citation]
cs, Text
raw) <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(F [Citation], Text)
forall (m :: * -> *) st a.
Monad m =>
ParsecT Sources st m a -> ParsecT Sources st m (a, Text)
withRaw (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(F [Citation], Text))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(F [Citation], Text)
forall a b. (a -> b) -> a -> b
$ ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation]))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall a b. (a -> b) -> a -> b
$ [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall (m :: * -> *). PandocMonad m => OrgParser m (F [Citation])
orgCite
, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall (m :: * -> *). PandocMonad m => OrgParser m (F [Citation])
orgRefCite
]
F Inlines -> OrgParser m (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines -> OrgParser m (F Inlines))
-> F Inlines -> OrgParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ ([Citation] -> Inlines -> Inlines)
-> Inlines -> [Citation] -> Inlines
forall a b c. (a -> b -> c) -> b -> a -> c
flip [Citation] -> Inlines -> Inlines
B.cite (Text -> Inlines
B.text Text
raw) ([Citation] -> Inlines) -> F [Citation] -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F [Citation]
cs
orgRefCite :: PandocMonad m => OrgParser m (F [Citation])
orgRefCite :: forall (m :: * -> *). PandocMonad m => OrgParser m (F [Citation])
orgRefCite = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation]))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall a b. (a -> b) -> a -> b
$ [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall (m :: * -> *). PandocMonad m => OrgParser m (F [Citation])
normalOrgRefCite
, (Citation -> [Citation])
-> Future OrgParserState Citation -> F [Citation]
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Citation -> [Citation] -> [Citation]
forall a. a -> [a] -> [a]
:[]) (Future OrgParserState Citation -> F [Citation])
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
forall (m :: * -> *).
PandocMonad m =>
OrgParser m (Future OrgParserState Citation)
linkLikeOrgRefCite
]
normalOrgRefCite :: PandocMonad m => OrgParser m (F [Citation])
normalOrgRefCite :: forall (m :: * -> *). PandocMonad m => OrgParser m (F [Citation])
normalOrgRefCite = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation]))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall a b. (a -> b) -> a -> b
$ do
CitationMode
mode <- OrgParser m CitationMode
forall (m :: * -> *). PandocMonad m => OrgParser m CitationMode
orgRefCiteMode
Future OrgParserState Citation
firstCitation <- CitationMode -> OrgParser m (Future OrgParserState Citation)
forall (m :: * -> *).
PandocMonad m =>
CitationMode -> OrgParser m (Future OrgParserState Citation)
orgRefCiteList CitationMode
mode
[Future OrgParserState Citation]
moreCitations <- OrgParser m (Future OrgParserState Citation)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
[Future OrgParserState Citation]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (OrgParser m (Future OrgParserState Citation)
-> OrgParser m (Future OrgParserState Citation)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (Future OrgParserState Citation)
-> OrgParser m (Future OrgParserState Citation))
-> OrgParser m (Future OrgParserState Citation)
-> OrgParser m (Future OrgParserState Citation)
forall a b. (a -> b) -> a -> b
$ Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m (Future OrgParserState Citation)
-> OrgParser m (Future OrgParserState Citation)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> CitationMode -> OrgParser m (Future OrgParserState Citation)
forall (m :: * -> *).
PandocMonad m =>
CitationMode -> OrgParser m (Future OrgParserState Citation)
orgRefCiteList CitationMode
mode)
F [Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F [Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation]))
-> ([Future OrgParserState Citation] -> F [Citation])
-> [Future OrgParserState Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Future OrgParserState Citation] -> F [Citation]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence ([Future OrgParserState Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation]))
-> [Future OrgParserState Citation]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F [Citation])
forall a b. (a -> b) -> a -> b
$ Future OrgParserState Citation
firstCitation Future OrgParserState Citation
-> [Future OrgParserState Citation]
-> [Future OrgParserState Citation]
forall a. a -> [a] -> [a]
: [Future OrgParserState Citation]
moreCitations
where
orgRefCiteList :: PandocMonad m => CitationMode -> OrgParser m (F Citation)
orgRefCiteList :: forall (m :: * -> *).
PandocMonad m =>
CitationMode -> OrgParser m (Future OrgParserState Citation)
orgRefCiteList CitationMode
citeMode = ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation))
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
forall a b. (a -> b) -> a -> b
$ do
Text
key <- OrgParser m Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
orgRefCiteKey
Citation
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF Citation
{ citationId :: Text
citationId = Text
key
, citationPrefix :: [Inline]
citationPrefix = [Inline]
forall a. Monoid a => a
mempty
, citationSuffix :: [Inline]
citationSuffix = [Inline]
forall a. Monoid a => a
mempty
, citationMode :: CitationMode
citationMode = CitationMode
citeMode
, citationNoteNum :: Int
citationNoteNum = Int
0
, citationHash :: Int
citationHash = Int
0
}
linkLikeOrgRefCite :: PandocMonad m => OrgParser m (F Citation)
linkLikeOrgRefCite :: forall (m :: * -> *).
PandocMonad m =>
OrgParser m (Future OrgParserState Citation)
linkLikeOrgRefCite = ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation))
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
forall a b. (a -> b) -> a -> b
$ do
[Char]
_ <- [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"[["
CitationMode
mode <- OrgParser m CitationMode
forall (m :: * -> *). PandocMonad m => OrgParser m CitationMode
orgRefCiteMode
Text
key <- OrgParser m Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
orgRefCiteKey
[Char]
_ <- [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"]["
F Inlines
pre <- F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"::")
Bool
spc <- Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar)
F Inlines
suf <- F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"]]")
Future OrgParserState Citation
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Future OrgParserState Citation
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation))
-> Future OrgParserState Citation
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Citation)
forall a b. (a -> b) -> a -> b
$ do
Inlines
pre' <- F Inlines
pre
Inlines
suf' <- F Inlines
suf
Citation -> Future OrgParserState Citation
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return Citation
{ citationId :: Text
citationId = Text
key
, citationPrefix :: [Inline]
citationPrefix = Inlines -> [Inline]
forall a. Many a -> [a]
B.toList Inlines
pre'
, citationSuffix :: [Inline]
citationSuffix = Inlines -> [Inline]
forall a. Many a -> [a]
B.toList (if Bool
spc then Inlines
B.space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
suf' else Inlines
suf')
, citationMode :: CitationMode
citationMode = CitationMode
mode
, citationNoteNum :: Int
citationNoteNum = Int
0
, citationHash :: Int
citationHash = Int
0
}
orgRefCiteKey :: PandocMonad m => OrgParser m Text
orgRefCiteKey :: forall (m :: * -> *). PandocMonad m => OrgParser m Text
orgRefCiteKey =
let citeKeySpecialChars :: [Char]
citeKeySpecialChars = [Char]
"-_:\\./" :: String
isCiteKeySpecialChar :: Char -> Bool
isCiteKeySpecialChar Char
c = Char
c Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char]
citeKeySpecialChars
isCiteKeyChar :: Char -> Bool
isCiteKeyChar Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char -> Bool
isCiteKeySpecialChar Char
c
endOfCitation :: ParsecT Sources u (ReaderT OrgParserLocal m) Char
endOfCitation = ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) [Char])
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isCiteKeySpecialChar
(Char -> Bool) -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy ((Char -> Bool)
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char)
-> (Char -> Bool)
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isCiteKeyChar
in ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ do
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'&')
(Char -> Bool)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy Char -> Bool
isCiteKeyChar ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
`many1TillChar` ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall {u}. ParsecT Sources u (ReaderT OrgParserLocal m) Char
endOfCitation
orgRefCiteMode :: PandocMonad m => OrgParser m CitationMode
orgRefCiteMode :: forall (m :: * -> *). PandocMonad m => OrgParser m CitationMode
orgRefCiteMode =
[ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ([ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode)
-> [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode
forall a b. (a -> b) -> a -> b
$ (([Char], CitationMode)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode)
-> [([Char], CitationMode)]
-> [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode]
forall a b. (a -> b) -> [a] -> [b]
map (\([Char]
s, CitationMode
mode) -> CitationMode
mode CitationMode
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) CitationMode
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
s ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':'))
[ ([Char]
"cite", CitationMode
AuthorInText)
, ([Char]
"citep", CitationMode
NormalCitation)
, ([Char]
"citep*", CitationMode
NormalCitation)
, ([Char]
"citet", CitationMode
AuthorInText)
, ([Char]
"citet*", CitationMode
AuthorInText)
, ([Char]
"citeyear", CitationMode
SuppressAuthor)
]
footnote :: PandocMonad m => OrgParser m (F Inlines)
= ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
F Inlines
note <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlineNote ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
referencedNote
Bool
withNote <- (ExportSettings -> Bool) -> OrgParser m Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportWithFootnotes
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ if Bool
withNote then F Inlines
note else F Inlines
forall a. Monoid a => a
mempty
inlineNote :: PandocMonad m => OrgParser m (F Inlines)
inlineNote :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlineNote = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
[Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"[fn:"
Text
ref <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':'
Future OrgParserState Blocks
note <- (Inlines -> Blocks) -> F Inlines -> Future OrgParserState Blocks
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Blocks
B.para (F Inlines -> Future OrgParserState Blocks)
-> ([F Inlines] -> F Inlines)
-> [F Inlines]
-> Future OrgParserState Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> Future OrgParserState Blocks)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future OrgParserState Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F 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 OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Bool
T.null Text
ref) (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$
OrgNoteRecord
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *).
PandocMonad m =>
OrgNoteRecord -> OrgParser m ()
addToNotesTable (Text
"fn:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ref, Future OrgParserState Blocks
note)
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Blocks -> Inlines
B.note (Blocks -> Inlines) -> Future OrgParserState Blocks -> F Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Future OrgParserState Blocks
note
referencedNote :: PandocMonad m => OrgParser m (F Inlines)
referencedNote :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
referencedNote = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Text
ref <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
noteMarker
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
OrgNoteTable
notes <- (OrgParserState -> OrgNoteTable)
-> Future OrgParserState OrgNoteTable
forall s a. (s -> a) -> Future s a
asksF OrgParserState -> OrgNoteTable
orgStateNotes'
case Text -> OrgNoteTable -> Maybe (Future OrgParserState Blocks)
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
ref OrgNoteTable
notes of
Maybe (Future OrgParserState Blocks)
Nothing -> Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.str (Text -> F Inlines) -> Text -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ref Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
Just Future OrgParserState Blocks
contents -> do
OrgParserState
st <- Future OrgParserState OrgParserState
forall s. Future s s
askF
let contents' :: Blocks
contents' = Future OrgParserState Blocks -> OrgParserState -> Blocks
forall s a. Future s a -> s -> a
runF Future OrgParserState Blocks
contents OrgParserState
st{ orgStateNotes' = [] }
Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Blocks -> Inlines
B.note Blocks
contents'
linkOrImage :: PandocMonad m => OrgParser m (F Inlines)
linkOrImage :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
linkOrImage = OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
explicitOrImageLink
OrgParser m (F Inlines)
-> OrgParser m (F Inlines) -> OrgParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
selflinkOrImage
OrgParser m (F Inlines)
-> OrgParser m (F Inlines) -> OrgParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
angleLink
OrgParser m (F Inlines)
-> OrgParser m (F Inlines) -> OrgParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
plainLink
OrgParser m (F Inlines) -> [Char] -> OrgParser m (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> [Char] -> ParsecT s u m a
<?> [Char]
"link or image"
explicitOrImageLink :: PandocMonad m => OrgParser m (F Inlines)
explicitOrImageLink :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
explicitOrImageLink = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'['
F Text
srcF <- Text -> OrgParser m (F Text)
forall (m :: * -> *). Text -> OrgParser m (F Text)
applyCustomLinkFormat (Text -> OrgParser m (F Text))
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> OrgParser m (F Text)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
possiblyEmptyLinkTarget
Text
descr <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
OrgParser m a -> OrgParser m b -> OrgParser m Text
enclosedRaw (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']')
F Inlines
titleF <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString ([F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline) Text
descr
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
']'
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Text
src <- F Text
srcF
Inlines
title <- F Inlines
titleF
case Text -> Maybe Text
cleanLinkText Text
descr of
Just Text
imgSrc | Text -> Bool
isImageFilename Text
imgSrc ->
Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> (Inlines -> Inlines) -> Inlines -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Inlines -> Inlines
B.link Text
src Text
"" (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.image Text
imgSrc Text
forall a. Monoid a => a
mempty Inlines
forall a. Monoid a => a
mempty
Maybe Text
_ ->
Text -> Inlines -> F Inlines
linkToInlinesF Text
src Inlines
title
selflinkOrImage :: PandocMonad m => OrgParser m (F Inlines)
selflinkOrImage :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
selflinkOrImage = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Text
target <- Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
linkTarget ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 -> Maybe Text
cleanLinkText Text
target of
Maybe Text
Nothing -> case Text -> Maybe (Char, Text)
T.uncons Text
target of
Just (Char
'#', Text
_) -> Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link Text
target Text
"" (Text -> Inlines
B.str Text
target)
Maybe (Char, Text)
_ -> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Text -> Inlines -> F Inlines
internalLink Text
target (Text -> Inlines
B.str Text
target)
Just Text
nonDocTgt -> if Text -> Bool
isImageFilename Text
nonDocTgt
then Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.image Text
nonDocTgt Text
"" Inlines
""
else Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link Text
nonDocTgt Text
"" (Text -> Inlines
B.str Text
target)
plainLink :: PandocMonad m => OrgParser m (F Inlines)
plainLink :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
plainLink = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
(Text
orig, Text
src) <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m (Text, Text)
uri
Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link Text
src Text
"" (Text -> Inlines
B.str Text
orig)
angleLink :: PandocMonad m => OrgParser m (F Inlines)
angleLink :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
angleLink = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'<'
F Inlines
link <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
plainLink
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'>'
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return F Inlines
link
linkTarget :: PandocMonad m => OrgParser m Text
linkTarget :: forall (m :: * -> *). PandocMonad m => OrgParser m Text
linkTarget = [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> Char
-> OrgParser m Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) a.
PandocMonad m =>
Char -> Char -> OrgParser m a -> OrgParser m [a]
enclosedByPair1 Char
'[' Char
']' ([Char] -> OrgParser 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[]")
possiblyEmptyLinkTarget :: PandocMonad m => OrgParser m Text
possiblyEmptyLinkTarget :: forall (m :: * -> *). PandocMonad m => OrgParser m Text
possiblyEmptyLinkTarget = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
linkTarget ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (Text
"" Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"[]")
applyCustomLinkFormat :: Text -> OrgParser m (F Text)
applyCustomLinkFormat :: forall (m :: * -> *). Text -> OrgParser m (F Text)
applyCustomLinkFormat Text
link = do
let (Text
linkType, Text
rest) = (Char -> Bool) -> Text -> (Text, Text)
T.break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') Text
link
F Text -> OrgParser m (F Text)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Text -> OrgParser m (F Text)) -> F Text -> OrgParser m (F Text)
forall a b. (a -> b) -> a -> b
$ do
Maybe (Text -> Text)
formatter <- Text -> Map Text (Text -> Text) -> Maybe (Text -> Text)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
linkType (Map Text (Text -> Text) -> Maybe (Text -> Text))
-> Future OrgParserState (Map Text (Text -> Text))
-> Future OrgParserState (Maybe (Text -> Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (OrgParserState -> Map Text (Text -> Text))
-> Future OrgParserState (Map Text (Text -> Text))
forall s a. (s -> a) -> Future s a
asksF OrgParserState -> Map Text (Text -> Text)
orgStateLinkFormatters
Text -> F Text
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> F Text) -> Text -> F Text
forall a b. (a -> b) -> a -> b
$ Text -> ((Text -> Text) -> Text) -> Maybe (Text -> Text) -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
link ((Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
1 Text
rest) Maybe (Text -> Text)
formatter
linkToInlinesF :: Text -> Inlines -> F Inlines
linkToInlinesF :: Text -> Inlines -> F Inlines
linkToInlinesF Text
linkStr =
case Text -> Maybe (Char, Text)
T.uncons Text
linkStr of
Maybe (Char, Text)
Nothing -> Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> F Inlines)
-> (Inlines -> Inlines) -> Inlines -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Inlines -> Inlines
B.link Text
forall a. Monoid a => a
mempty Text
""
Just (Char
'#', Text
_) -> Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> F Inlines)
-> (Inlines -> Inlines) -> Inlines -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Inlines -> Inlines
B.link Text
linkStr Text
""
Maybe (Char, Text)
_ -> case Text -> Maybe Text
cleanLinkText Text
linkStr of
Just Text
extTgt -> Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines)
-> (Inlines -> Inlines) -> Inlines -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Inlines -> Inlines
B.link Text
extTgt Text
""
Maybe Text
Nothing -> Text -> Inlines -> F Inlines
internalLink Text
linkStr
internalLink :: Text -> Inlines -> F Inlines
internalLink :: Text -> Inlines -> F Inlines
internalLink Text
link Inlines
title = do
[Text]
ids <- (OrgParserState -> [Text]) -> Future OrgParserState [Text]
forall s a. (s -> a) -> Future s a
asksF OrgParserState -> [Text]
orgStateAnchorIds
if Text
link Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
ids
then Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link (Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
link) Text
"" Inlines
title
else let attr' :: (Text, [Text], [(Text, Text)])
attr' = (Text
"", [Text
"spurious-link"] , [(Text
"target", Text
link)])
in Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> Inlines -> F Inlines
forall a b. (a -> b) -> a -> b
$ (Text, [Text], [(Text, Text)]) -> Inlines -> Inlines
B.spanWith (Text, [Text], [(Text, Text)])
attr' (Inlines -> Inlines
B.emph Inlines
title)
anchor :: PandocMonad m => OrgParser m (F Inlines)
anchor :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
anchor = do
Text
anchorId <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgAnchor
Inlines -> OrgParser m (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Inlines -> OrgParser m (F Inlines))
-> Inlines -> OrgParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ (Text, [Text], [(Text, Text)]) -> Inlines -> Inlines
B.spanWith (Text -> Text
solidify Text
anchorId, [], []) Inlines
forall a. Monoid a => a
mempty
solidify :: Text -> Text
solidify :: Text -> Text
solidify = (Char -> Char) -> Text -> Text
T.map Char -> Char
replaceSpecialChar
where replaceSpecialChar :: Char -> Char
replaceSpecialChar Char
c
| Char -> Bool
isAlphaNum Char
c = Char
c
| Char
c Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ([Char]
"_.-:" :: String) = Char
c
| Bool
otherwise = Char
'-'
inlineCodeBlock :: PandocMonad m => OrgParser m (F Inlines)
inlineCodeBlock :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlineCodeBlock = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
[Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"src_"
Text
lang <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). Monad m => OrgParser m Char
orgArgWordChar
[(Text, Text)]
opts <- [(Text, Text)]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option [] (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Char
-> Char
-> OrgParser m (Text, Text)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [(Text, Text)]
forall (m :: * -> *) a.
PandocMonad m =>
Char -> Char -> OrgParser m a -> OrgParser m [a]
enclosedByPair Char
'[' Char
']' OrgParser m (Text, Text)
forall (m :: * -> *). PandocMonad m => OrgParser m (Text, Text)
inlineBlockOption
Text
inlineCode <- [Char] -> Text
T.pack ([Char] -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) a.
PandocMonad m =>
Char -> Char -> OrgParser m a -> OrgParser m [a]
enclosedByPair1 Char
'{' Char
'}' ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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")
let attrClasses :: [Text]
attrClasses = [Text -> Text
translateLang Text
lang]
let attrKeyVal :: [(Text, Text)]
attrKeyVal = Text -> [(Text, Text)]
originalLang Text
lang [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)]
opts
let codeInlineBlck :: Inlines
codeInlineBlck = (Text, [Text], [(Text, Text)]) -> Text -> Inlines
B.codeWith (Text
"", [Text]
attrClasses, [(Text, Text)]
attrKeyVal) Text
inlineCode
Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ if [(Text, Text)] -> Bool
exportsCode [(Text, Text)]
opts then Inlines
codeInlineBlck else Inlines
forall a. Monoid a => a
mempty
where
inlineBlockOption :: PandocMonad m => OrgParser m (Text, Text)
inlineBlockOption :: forall (m :: * -> *). PandocMonad m => OrgParser m (Text, Text)
inlineBlockOption = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text, Text))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
forall a b. (a -> b) -> a -> b
$ do
Text
argKey <- OrgParser m Text
forall (m :: * -> *). Monad m => OrgParser m Text
orgArgKey
Text
paramValue <- Text -> OrgParser m Text -> OrgParser 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
"yes" OrgParser m Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
orgInlineParamValue
(Text, Text)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text, Text)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
argKey, Text
paramValue)
orgInlineParamValue :: PandocMonad m => OrgParser m Text
orgInlineParamValue :: forall (m :: * -> *). PandocMonad m => OrgParser m Text
orgInlineParamValue = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 ]")
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
skipSpaces
emphasizedText :: PandocMonad m => OrgParser m (F Inlines)
emphasizedText :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
emphasizedText = do
OrgParserState
state <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> Bool)
-> OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExportSettings -> Bool
exportEmphasizedText (ExportSettings -> Bool)
-> (OrgParserState -> ExportSettings) -> OrgParserState -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> ExportSettings
orgStateExportSettings (OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ OrgParserState
state
OrgParser m (F Inlines) -> OrgParser m (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m (F Inlines) -> OrgParser m (F Inlines))
-> OrgParser m (F Inlines) -> OrgParser m (F Inlines)
forall a b. (a -> b) -> a -> b
$ [OrgParser m (F Inlines)] -> OrgParser m (F Inlines)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
emph
, OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
strong
, OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
strikeout
, OrgParser m (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
underline
]
enclosedByPair :: PandocMonad m
=> Char
-> Char
-> OrgParser m a
-> OrgParser m [a]
enclosedByPair :: forall (m :: * -> *) a.
PandocMonad m =>
Char -> Char -> OrgParser m a -> OrgParser m [a]
enclosedByPair Char
s Char
e OrgParser m a
p = Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
s ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [a]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [a]
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [a]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill OrgParser m a
p (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
e)
enclosedByPair1 :: PandocMonad m
=> Char
-> Char
-> OrgParser m a
-> OrgParser m [a]
enclosedByPair1 :: forall (m :: * -> *) a.
PandocMonad m =>
Char -> Char -> OrgParser m a -> OrgParser m [a]
enclosedByPair1 Char
s Char
e OrgParser m a
p = Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
s ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [a]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [a]
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> OrgParser m a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParser m a
p (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
e)
emph :: PandocMonad m => OrgParser m (F Inlines)
emph :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
emph = (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.emph (F Inlines -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> OrgParser m (F Inlines)
emphasisBetween Char
'/'
strong :: PandocMonad m => OrgParser m (F Inlines)
strong :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
strong = (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.strong (F Inlines -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> OrgParser m (F Inlines)
emphasisBetween Char
'*'
strikeout :: PandocMonad m => OrgParser m (F Inlines)
strikeout :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
strikeout = (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.strikeout (F Inlines -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> OrgParser m (F Inlines)
emphasisBetween Char
'+'
underline :: PandocMonad m => OrgParser m (F Inlines)
underline :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
underline = (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.underline (F Inlines -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *).
PandocMonad m =>
Char -> OrgParser m (F Inlines)
emphasisBetween Char
'_'
verbatim :: PandocMonad m => OrgParser m (F Inlines)
verbatim :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
verbatim = Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text, [Text], [(Text, Text)]) -> Text -> Inlines
B.codeWith (Text
"", [Text
"verbatim"], []) (Text -> F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Text
verbatimBetween Char
'='
code :: PandocMonad m => OrgParser m (F Inlines)
code :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
code = Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.code (Text -> F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Text
verbatimBetween Char
'~'
subscript :: PandocMonad m => OrgParser m (F Inlines)
subscript :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
subscript = (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.subscript (F Inlines -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
subOrSuperExpr)
superscript :: PandocMonad m => OrgParser m (F Inlines)
superscript :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
superscript = (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.superscript (F Inlines -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
subOrSuperExpr)
math :: PandocMonad m => OrgParser m (F Inlines)
math :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
math = Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.math (Text -> F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Text
math1CharBetween Char
'$'
, Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Text
mathTextBetween Char
'$'
, Text
-> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> OrgParser m Text
rawMathBetween Text
"\\(" Text
"\\)"
]
displayMath :: PandocMonad m => OrgParser m (F Inlines)
displayMath :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
displayMath = Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.displayMath (Text -> F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Text
-> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> OrgParser m Text
rawMathBetween Text
"\\[" Text
"\\]"
, Text
-> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> OrgParser m Text
rawMathBetween Text
"$$" Text
"$$"
]
updatePositions :: PandocMonad m
=> Char
-> OrgParser m Char
updatePositions :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions Char
c = do
OrgParserState
st <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let emphasisPreChars :: [Char]
emphasisPreChars = OrgParserState -> [Char]
orgStateEmphasisPreChars OrgParserState
st
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Char
c Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char]
emphasisPreChars) ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastPreCharPos
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Char
c Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char]
emphasisForbiddenBorderChars) ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastForbiddenCharPos
Char -> OrgParser m Char
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Char
c
symbol :: PandocMonad m => OrgParser m (F Inlines)
symbol :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
symbol = Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Char -> Inlines) -> Char -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 -> F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
specialChars ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> (Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions)
emphasisBetween :: PandocMonad m
=> Char
-> OrgParser m (F Inlines)
emphasisBetween :: forall (m :: * -> *).
PandocMonad m =>
Char -> OrgParser m (F Inlines)
emphasisBetween Char
c = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Int -> OrgParser m ()
forall (m :: * -> *). PandocMonad m => Int -> OrgParser m ()
startEmphasisNewlinesCounting Int
emphasisAllowedNewlines
F Inlines
res <- OrgParser m Char
-> OrgParser m Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
OrgParser m a -> OrgParser m b -> OrgParser m (F Inlines)
enclosedInlines (Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
emphasisStart Char
c) (Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
emphasisEnd Char
c)
Bool
isTopLevelEmphasis <- [Char] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Char] -> Bool)
-> (OrgParserState -> [Char]) -> OrgParserState -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> [Char]
orgStateEmphasisCharStack (OrgParserState -> Bool)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> OrgParser m () -> OrgParser m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isTopLevelEmphasis
OrgParser m ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
resetEmphasisNewlines
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return F Inlines
res
verbatimBetween :: PandocMonad m
=> Char
-> OrgParser m Text
verbatimBetween :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Text
verbatimBetween Char
c = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$
Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
emphasisStart Char
c OrgParser m Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Int
-> OrgParser m Char
-> OrgParser m Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *) a.
PandocMonad m =>
Int -> OrgParser m Char -> OrgParser m a -> OrgParser m Text
many1TillNOrLessNewlines Int
1 OrgParser m Char
verbatimChar (Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
emphasisEnd Char
c)
where
verbatimChar :: OrgParser m Char
verbatimChar = [Char] -> OrgParser 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" OrgParser m Char -> (Char -> OrgParser m Char) -> OrgParser m Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions
mathTextBetween :: PandocMonad m
=> Char
-> OrgParser m Text
mathTextBetween :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Text
mathTextBetween Char
c = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ do
Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
mathStart Char
c
Text
body <- Int
-> OrgParser m Char
-> OrgParser m Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *) a.
PandocMonad m =>
Int -> OrgParser m Char -> OrgParser m a -> OrgParser m Text
many1TillNOrLessNewlines Int
mathAllowedNewlines
([Char] -> OrgParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf (Char
cChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
"\n\r"))
(OrgParser m Char -> OrgParser m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (OrgParser m Char -> OrgParser m Char)
-> OrgParser m Char -> OrgParser m Char
forall a b. (a -> b) -> a -> b
$ Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
mathEnd Char
c)
Char
final <- Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
mathEnd Char
c
Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ Text -> Char -> Text
T.snoc Text
body Char
final
math1CharBetween :: PandocMonad m
=> Char
-> OrgParser m Text
math1CharBetween :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Text
math1CharBetween Char
c = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ do
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
c
Char
res <- [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ Char
cChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
mathForbiddenBorderChars
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
mathPostChars)
Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
res
rawMathBetween :: PandocMonad m
=> Text
-> Text
-> OrgParser m Text
rawMathBetween :: forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> OrgParser m Text
rawMathBetween Text
s Text
e = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
s ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
e)
emphasisStart :: PandocMonad m => Char -> OrgParser m Char
emphasisStart :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
emphasisStart Char
c = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ do
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *). PandocMonad m => OrgParser m Bool
afterEmphasisPreChar
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
emphasisForbiddenBorderChars)
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m ()
pushToInlineCharStack Char
c
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastPreCharPos
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Char
c
emphasisEnd :: PandocMonad m => Char -> OrgParser m Char
emphasisEnd :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
emphasisEnd Char
c = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ do
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *). PandocMonad m => OrgParser m Bool
notAfterForbiddenBorderChar
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
acceptablePostChars
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) a st.
(Stream s m a, HasLastStrPosition st) =>
ParsecT s st m ()
updateLastStrPos
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *). PandocMonad m => OrgParser m ()
popInlineCharStack
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Char
c
where
acceptablePostChars :: ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
acceptablePostChars = do
[Char]
emphasisPostChars <- OrgParserState -> [Char]
orgStateEmphasisPostChars (OrgParserState -> [Char])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *). PandocMonad m => OrgParser m [Char]
surroundingEmphasisChar ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[Char]
x -> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf ([Char]
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
emphasisPostChars)
mathStart :: PandocMonad m => Char -> OrgParser m Char
mathStart :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
mathStart Char
c = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall b s (m :: * -> *) a st.
(Show b, Stream s m a) =>
ParsecT s st m b -> ParsecT s st m ()
notFollowedBy' ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf (Char
cChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
mathForbiddenBorderChars))
mathEnd :: PandocMonad m => Char -> OrgParser m Char
mathEnd :: forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
mathEnd Char
c = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ do
Char
res <- [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf (Char
cChar -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
mathForbiddenBorderChars)
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> () ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
mathPostChars)
Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Char
res
enclosedInlines :: (PandocMonad m, Show b) => OrgParser m a
-> OrgParser m b
-> OrgParser m (F Inlines)
enclosedInlines :: forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
OrgParser m a -> OrgParser m b -> OrgParser m (F Inlines)
enclosedInlines OrgParser m a
start OrgParser m b
end = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$
F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OrgParser m a
-> OrgParser m b
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
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 OrgParser m a
start OrgParser m b
end ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline
enclosedRaw :: (PandocMonad m, Show b) => OrgParser m a
-> OrgParser m b
-> OrgParser m Text
enclosedRaw :: forall (m :: * -> *) b a.
(PandocMonad m, Show b) =>
OrgParser m a -> OrgParser m b -> OrgParser m Text
enclosedRaw OrgParser m a
start OrgParser m b
end = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$
OrgParser m a
start OrgParser m a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
onSingleLine ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
spanningTwoLines)
where onSingleLine :: ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
onSingleLine = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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") OrgParser m b
end
spanningTwoLines :: ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
spanningTwoLines = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (m :: * -> *). Monad m => OrgParser m Text
anyLine ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> (Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
f -> Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend (Text
f Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ") (Text -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
onSingleLine
many1TillNOrLessNewlines :: PandocMonad m => Int
-> OrgParser m Char
-> OrgParser m a
-> OrgParser m Text
many1TillNOrLessNewlines :: forall (m :: * -> *) a.
PandocMonad m =>
Int -> OrgParser m Char -> OrgParser m a -> OrgParser m Text
many1TillNOrLessNewlines Int
n OrgParser m Char
p OrgParser m a
end = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$
Maybe Int
-> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall {a}.
(Eq a, Num a) =>
Maybe a
-> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
nMoreLines (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n) [Char]
forall a. Monoid a => a
mempty ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ([Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall {f :: * -> *}. Alternative f => [Char] -> f Text
oneOrMore
where
nMoreLines :: Maybe a
-> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
nMoreLines Maybe a
Nothing [Char]
cs = [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
cs
nMoreLines (Just a
0) [Char]
cs = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b. (a -> b) -> a -> b
$ ([Char]
cs [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++) ([Char] -> [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
finalLine
nMoreLines Maybe a
k [Char]
cs = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b. (a -> b) -> a -> b
$ (Maybe a
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
forall {p} {a}.
p
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
final Maybe a
k [Char]
cs ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe a
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
forall {b} {f :: * -> *}.
(Num b, Functor f) =>
f b
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (f b, [Char])
rest Maybe a
k [Char]
cs)
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
-> ((Maybe a, [Char])
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Maybe a
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Char])
-> (Maybe a, [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Maybe a
-> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
nMoreLines
final :: p
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
final p
_ [Char]
cs = (\[Char]
x -> (Maybe a
forall a. Maybe a
Nothing, [Char]
cs [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
x)) ([Char] -> (Maybe a, [Char]))
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe a, [Char])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
finalLine
rest :: f b
-> [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (f b, [Char])
rest f b
m [Char]
cs = (\[Char]
x -> (b -> b
forall {a}. Num a => a -> a
minus1 (b -> b) -> f b -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f b
m, [Char]
cs [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
x [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"\n")) ([Char] -> (f b, [Char]))
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (f b, [Char])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (OrgParser m Char
-> OrgParser m Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill OrgParser m Char
p OrgParser m Char
forall (m :: * -> *). Monad m => OrgParser m Char
newline)
finalLine :: ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
finalLine = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b. (a -> b) -> a -> b
$ OrgParser m Char
-> OrgParser m a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
manyTill OrgParser m Char
p OrgParser m a
end
minus1 :: a -> a
minus1 a
k = a
k a -> a -> a
forall a. Num a => a -> a -> a
- a
1
oneOrMore :: [Char] -> f Text
oneOrMore [Char]
cs = [Char] -> Text
T.pack [Char]
cs Text -> f () -> f Text
forall a b. a -> f b -> f a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> f ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Char] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Char]
cs)
emphasisForbiddenBorderChars :: [Char]
emphasisForbiddenBorderChars :: [Char]
emphasisForbiddenBorderChars = [Char]
"\t\n\r \x200B"
emphasisAllowedNewlines :: Int
emphasisAllowedNewlines :: Int
emphasisAllowedNewlines = Int
1
mathPostChars :: [Char]
mathPostChars :: [Char]
mathPostChars = [Char]
"\t\n \"'),-.:;?"
mathForbiddenBorderChars :: [Char]
mathForbiddenBorderChars :: [Char]
mathForbiddenBorderChars = [Char]
"\t\n\r ,;.$"
mathAllowedNewlines :: Int
mathAllowedNewlines :: Int
mathAllowedNewlines = Int
2
afterEmphasisPreChar :: PandocMonad m => OrgParser m Bool
afterEmphasisPreChar :: forall (m :: * -> *). PandocMonad m => OrgParser m Bool
afterEmphasisPreChar = do
SourcePos
pos <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
Maybe SourcePos
lastPrePos <- OrgParserState -> Maybe SourcePos
orgStateLastPreCharPos (OrgParserState -> Maybe SourcePos)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe SourcePos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> OrgParser m Bool
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> OrgParser m Bool) -> Bool -> OrgParser m Bool
forall a b. (a -> b) -> a -> b
$ Bool -> (SourcePos -> Bool) -> Maybe SourcePos -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (SourcePos -> SourcePos -> Bool
forall a. Eq a => a -> a -> Bool
== SourcePos
pos) Maybe SourcePos
lastPrePos
notAfterForbiddenBorderChar :: PandocMonad m => OrgParser m Bool
notAfterForbiddenBorderChar :: forall (m :: * -> *). PandocMonad m => OrgParser m Bool
notAfterForbiddenBorderChar = do
SourcePos
pos <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
Maybe SourcePos
lastFBCPos <- OrgParserState -> Maybe SourcePos
orgStateLastForbiddenCharPos (OrgParserState -> Maybe SourcePos)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Maybe SourcePos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> OrgParser m Bool
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> OrgParser m Bool) -> Bool -> OrgParser m Bool
forall a b. (a -> b) -> a -> b
$ Maybe SourcePos
lastFBCPos Maybe SourcePos -> Maybe SourcePos -> Bool
forall a. Eq a => a -> a -> Bool
/= SourcePos -> Maybe SourcePos
forall a. a -> Maybe a
Just SourcePos
pos
subOrSuperExpr :: PandocMonad m => OrgParser m (F Inlines)
subOrSuperExpr :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
subOrSuperExpr = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
simpleSubOrSuperText ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
([ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Char
-> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
Char -> Char -> ParsecT s st m Text -> ParsecT s st m Text
charsInBalanced Char
'{' Char
'}' (Char -> Text
T.singleton (Char -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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")
, (Char, Char) -> Text -> Text
enclosing (Char
'(', Char
')') (Text -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char
-> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
Char -> Char -> ParsecT s st m Text -> ParsecT s st m Text
charsInBalanced Char
'(' Char
')' (Char -> Text
T.singleton (Char -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Text
-> (Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> (a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString ([F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline))
where enclosing :: (Char, Char) -> Text -> Text
enclosing (Char
left, Char
right) Text
s = Char -> Text -> Text
T.cons Char
left (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Char -> Text
T.snoc Text
s Char
right
simpleSubOrSuperText :: PandocMonad m => OrgParser m (F Inlines)
simpleSubOrSuperText :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
simpleSubOrSuperText = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
OrgParserState
state <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> Bool)
-> OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExportSettings -> Bool
exportSubSuperscripts (ExportSettings -> Bool)
-> (OrgParserState -> ExportSettings) -> OrgParserState -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OrgParserState -> ExportSettings
orgStateExportSettings (OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ OrgParserState
state
Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> F Inlines) -> (Text -> Inlines) -> Text -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.str (Text -> F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
[ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) u.
(Stream s m Char, UpdateSourcePos s Char) =>
Text -> ParsecT s u m Text
textStr Text
"*"
, Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend (Text -> Text -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) (Text -> Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) (a -> b)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
many1Char ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum
]
inlineLaTeX :: PandocMonad m => OrgParser m (F Inlines)
inlineLaTeX :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inlineLaTeX = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Text
cmd <- OrgParser m Text
forall (m :: * -> *). PandocMonad m => OrgParser m Text
inlineLaTeXCommand
TeXExport
texOpt <- (ExportSettings -> TeXExport) -> OrgParser m TeXExport
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> TeXExport
exportWithLatex
Bool
allowEntities <- (ExportSettings -> Bool) -> OrgParser m Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportWithEntities
Maybe Inlines
ils <- Text -> TeXExport -> OrgParser m (Maybe Inlines)
forall (m :: * -> *).
PandocMonad m =>
Text -> TeXExport -> OrgParser m (Maybe Inlines)
parseAsInlineLaTeX Text
cmd TeXExport
texOpt
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> (Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Maybe Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Maybe Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Maybe Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$
Bool -> Text -> Maybe Inlines
parseAsMathMLSym Bool
allowEntities Text
cmd Maybe Inlines -> Maybe Inlines -> Maybe Inlines
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
Text -> TeXExport -> Maybe Inlines
parseAsMath Text
cmd TeXExport
texOpt Maybe Inlines -> Maybe Inlines -> Maybe Inlines
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
Maybe Inlines
ils
where
parseAsInlineLaTeX :: PandocMonad m
=> Text -> TeXExport -> OrgParser m (Maybe Inlines)
parseAsInlineLaTeX :: forall (m :: * -> *).
PandocMonad m =>
Text -> TeXExport -> OrgParser m (Maybe Inlines)
parseAsInlineLaTeX Text
cs = \case
TeXExport
TeXExport -> Either ParseError Inlines -> Maybe Inlines
forall a b. Either a b -> Maybe b
maybeRight (Either ParseError Inlines -> Maybe Inlines)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Either ParseError Inlines)
-> OrgParser m (Maybe Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources
ParserState
(ParsecT Sources OrgParserState (ReaderT OrgParserLocal m))
Inlines
-> ParserState
-> [Char]
-> Sources
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Either ParseError Inlines)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> [Char] -> s -> m (Either ParseError a)
runParserT ParsecT
Sources
ParserState
(ParsecT Sources OrgParserState (ReaderT OrgParserLocal m))
Inlines
forall (m :: * -> *).
PandocMonad m =>
ParsecT Sources ParserState m Inlines
inlineCommand ParserState
state [Char]
"" (Text -> Sources
forall a. ToSources a => a -> Sources
toSources Text
cs)
TeXExport
TeXIgnore -> Maybe Inlines -> OrgParser m (Maybe Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just Inlines
forall a. Monoid a => a
mempty)
TeXExport
TeXVerbatim -> Maybe Inlines -> OrgParser m (Maybe Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just (Inlines -> Maybe Inlines) -> Inlines -> Maybe Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
cs)
parseAsMathMLSym :: Bool -> Text -> Maybe Inlines
parseAsMathMLSym :: Bool -> Text -> Maybe Inlines
parseAsMathMLSym Bool
allowEntities Text
cs = do
let clean :: Text -> Text
clean = (Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> [Char] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ([Char]
"{}" :: String)) (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> Text
T.drop Int
1
case Text -> Inlines
B.str (Text -> Inlines) -> Maybe Text -> Maybe Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Text
MathMLEntityMap.getUnicode (Text -> Text
clean Text
cs) of
Just Inlines
_ | Bool -> Bool
not Bool
allowEntities -> Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just (Inlines -> Maybe Inlines) -> Inlines -> Maybe Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
cs
Maybe Inlines
x -> Maybe Inlines
x
state :: ParserState
state :: ParserState
state = ParserState
forall a. Default a => a
def{ stateOptions = def{ readerExtensions =
enableExtension Ext_raw_tex (readerExtensions def) } }
parseAsMath :: Text -> TeXExport -> Maybe Inlines
parseAsMath :: Text -> TeXExport -> Maybe Inlines
parseAsMath Text
cs = \case
TeXExport
TeXExport -> Either Text [Exp] -> Maybe [Exp]
forall a b. Either a b -> Maybe b
maybeRight (Text -> Either Text [Exp]
readTeX Text
cs) Maybe [Exp] -> ([Exp] -> Maybe Inlines) -> Maybe Inlines
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
([Inline] -> Inlines) -> Maybe [Inline] -> Maybe Inlines
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Inline] -> Inlines
forall a. [a] -> Many a
B.fromList (Maybe [Inline] -> Maybe Inlines)
-> ([Exp] -> Maybe [Inline]) -> [Exp] -> Maybe Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DisplayType -> [Exp] -> Maybe [Inline]
writePandoc DisplayType
DisplayInline
TeXExport
TeXIgnore -> Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just Inlines
forall a. Monoid a => a
mempty
TeXExport
TeXVerbatim -> Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just (Inlines -> Maybe Inlines) -> Inlines -> Maybe Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
cs
maybeRight :: Either a b -> Maybe b
maybeRight :: forall a b. Either a b -> Maybe b
maybeRight = (a -> Maybe b) -> (b -> Maybe b) -> Either a b -> Maybe b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe b -> a -> Maybe b
forall a b. a -> b -> a
const Maybe b
forall a. Maybe a
Nothing) b -> Maybe b
forall a. a -> Maybe a
Just
inlineLaTeXCommand :: PandocMonad m => OrgParser m Text
inlineLaTeXCommand :: forall (m :: * -> *). PandocMonad m => OrgParser m Text
inlineLaTeXCommand = ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ do
Sources
rest <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Sources
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
OrgParserState
st <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Either ParseError Text
parsed <- (ReaderT OrgParserLocal m (Either ParseError Text)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Either ParseError Text)
forall (m :: * -> *) a.
Monad m =>
m a -> ParsecT Sources OrgParserState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (ReaderT OrgParserLocal m (Either ParseError Text)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Either ParseError Text))
-> (m (Either ParseError Text)
-> ReaderT OrgParserLocal m (Either ParseError Text))
-> m (Either ParseError Text)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Either ParseError Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either ParseError Text)
-> ReaderT OrgParserLocal m (Either ParseError Text)
forall (m :: * -> *) a.
Monad m =>
m a -> ReaderT OrgParserLocal m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift) (m (Either ParseError Text)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Either ParseError Text))
-> m (Either ParseError Text)
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Either ParseError Text)
forall a b. (a -> b) -> a -> b
$ ParsecT Sources OrgParserState m Text
-> OrgParserState
-> [Char]
-> Sources
-> m (Either ParseError Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> [Char] -> s -> m (Either ParseError a)
runParserT ParsecT Sources OrgParserState m Text
forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
ParsecT Sources s m Text
rawLaTeXInline OrgParserState
st [Char]
"source" Sources
rest
case Either ParseError Text
parsed of
Right Text
cs -> do
let cmdNoSpc :: Text
cmdNoSpc = (Char -> Bool) -> Text -> Text
T.dropWhileEnd Char -> Bool
isSpace Text
cs
let len :: Int
len = Text -> Int
T.length Text
cmdNoSpc
Int
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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
len ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar
Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
cmdNoSpc
Either ParseError Text
_ -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall a.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
exportSnippet :: PandocMonad m => OrgParser m (F Inlines)
exportSnippet :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
exportSnippet = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
[Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"@@"
Text
format <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall end s (m :: * -> *) t st.
(Show end, Stream s m t) =>
ParsecT s st m Char -> ParsecT s st m end -> ParsecT s st m Text
many1TillChar (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':')
Text
snippet <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [Char])
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"@@")
Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines
B.rawInline Text
format Text
snippet
macro :: PandocMonad m => OrgParser m (F Inlines)
macro :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
macro = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Int
recursionDepth <- OrgParserState -> Int
orgStateMacroDepth (OrgParserState -> Int)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> Bool
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ Int
recursionDepth Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
15
[Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
"{{{"
Text
name <- ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall s (m :: * -> *) t st.
Stream s m t =>
ParsecT s st m Char -> ParsecT s st m Text
manyChar ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum
[Text]
args <- ([] [Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Text]
forall a b.
a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Text]
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
forall {st}. ParsecT Sources st (ReaderT OrgParserLocal m) Text
argument ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Text
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Text]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
`sepBy` Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) [Text]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Text]
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) [Char]
forall {u}. ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
eoa
Maybe MacroExpander
expander <- Text -> OrgParserState -> Maybe MacroExpander
lookupMacro Text
name (OrgParserState -> Maybe MacroExpander)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Maybe MacroExpander)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) OrgParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
case Maybe MacroExpander
expander of
Maybe MacroExpander
Nothing -> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
Just MacroExpander
fn -> do
(OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s -> OrgParserState
s { orgStateMacroDepth = recursionDepth + 1 }
F Inlines
res <- ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *) a.
Monad m =>
OrgParser m a -> Text -> OrgParser m a
parseFromString ([F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline) (Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> Text
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ MacroExpander
fn [Text]
args
(OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ())
-> (OrgParserState -> OrgParserState)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) ()
forall a b. (a -> b) -> a -> b
$ \OrgParserState
s -> OrgParserState
s { orgStateMacroDepth = recursionDepth }
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return F Inlines
res
where
argument :: ParsecT Sources st (ReaderT OrgParserLocal m) Text
argument = ParsecT Sources st (ReaderT OrgParserLocal m) Char
-> ParsecT Sources st (ReaderT OrgParserLocal 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 (ReaderT OrgParserLocal m) Char
-> ParsecT Sources st (ReaderT OrgParserLocal m) Text)
-> ParsecT Sources st (ReaderT OrgParserLocal m) Char
-> ParsecT Sources st (ReaderT OrgParserLocal m) Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources st (ReaderT OrgParserLocal m) [Char]
-> ParsecT Sources st (ReaderT OrgParserLocal 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 st (ReaderT OrgParserLocal m) [Char]
forall {u}. ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
eoa ParsecT Sources st (ReaderT OrgParserLocal m) ()
-> ParsecT Sources st (ReaderT OrgParserLocal m) Char
-> ParsecT Sources st (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources st (ReaderT OrgParserLocal m) a
-> ParsecT Sources st (ReaderT OrgParserLocal m) b
-> ParsecT Sources st (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ParsecT Sources st (ReaderT OrgParserLocal m) Char
forall {u}. ParsecT Sources u (ReaderT OrgParserLocal m) Char
escapedComma ParsecT Sources st (ReaderT OrgParserLocal m) Char
-> ParsecT Sources st (ReaderT OrgParserLocal m) Char
-> ParsecT Sources st (ReaderT OrgParserLocal 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 st (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
noneOf [Char]
",")
escapedComma :: ParsecT Sources u (ReaderT OrgParserLocal m) Char
escapedComma = ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char)
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources u (ReaderT OrgParserLocal 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 (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
-> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources u (ReaderT OrgParserLocal m) a
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
-> ParsecT Sources u (ReaderT OrgParserLocal m) b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [Char] -> ParsecT Sources u (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m Char
oneOf [Char]
",\\"
eoa :: ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
eoa = [Char] -> ParsecT Sources u (ReaderT OrgParserLocal m) [Char]
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
[Char] -> ParsecT s u m [Char]
string [Char]
")}}}"
smart :: PandocMonad m => OrgParser m (F Inlines)
smart :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
smart = [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
doubleQuoted, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
singleQuoted, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall {s}.
ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future s Inlines)
orgApostrophe, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
orgDash, ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
orgEllipses]
where
orgDash :: ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
orgDash = do
Bool -> OrgParser m ()
forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m ()
guardOrSmartEnabled (Bool -> OrgParser m ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> OrgParser m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (ExportSettings -> Bool)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportSpecialStrings
Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Inlines
forall st s (m :: * -> *).
(HasReaderOptions st, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines
dash ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions Char
'-'
orgEllipses :: ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
orgEllipses = do
Bool -> OrgParser m ()
forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m ()
guardOrSmartEnabled (Bool -> OrgParser m ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> OrgParser m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (ExportSettings -> Bool)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportSpecialStrings
Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Inlines
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Inlines
ellipses ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions Char
'.'
orgApostrophe :: ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future s Inlines)
orgApostrophe = do
Extension -> OrgParser m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_smart
(Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\8217') ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastPreCharPos
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
-> OrgParser m ()
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Char
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastForbiddenCharPos
Inlines
-> ParsecT
Sources
OrgParserState
(ReaderT OrgParserLocal m)
(Future s Inlines)
forall (m :: * -> *) a s. Monad m => a -> m (Future s a)
returnF (Text -> Inlines
B.str Text
"\x2019")
guardOrSmartEnabled :: PandocMonad m => Bool -> OrgParser m ()
guardOrSmartEnabled :: forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m ()
guardOrSmartEnabled Bool
b = do
Bool
smartExtension <- Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_smart (Extensions -> Bool)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Extensions
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ReaderOptions -> Extensions)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParsecT s st m b
forall s (m :: * -> *) t b.
Stream s m t =>
(ReaderOptions -> b) -> ParsecT s OrgParserState m b
getOption ReaderOptions -> Extensions
readerExtensions
Bool -> OrgParser m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool
b Bool -> Bool -> Bool
|| Bool
smartExtension)
singleQuoted :: PandocMonad m => OrgParser m (F Inlines)
singleQuoted :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
singleQuoted = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Bool -> OrgParser m ()
forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m ()
guardOrSmartEnabled (Bool -> OrgParser m ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> OrgParser m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (ExportSettings -> Bool)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportSmartQuotes
OrgParser m ()
forall st (m :: * -> *) s.
(HasLastStrPosition st, HasQuoteContext st m, Stream s m Char,
UpdateSourcePos s Char) =>
ParsecT s st m ()
singleQuoteStart
Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions Char
'\''
QuoteContext
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s a.
QuoteContext
-> ParsecT s OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT s OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$
(Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.singleQuoted (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines -> F Inlines)
-> ([F Inlines] -> F Inlines) -> [F Inlines] -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> OrgParser m ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F 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 OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline (OrgParser m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
singleQuoteEnd OrgParser m () -> OrgParser m Char -> OrgParser m ()
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions Char
'\'')
doubleQuoted :: PandocMonad m => OrgParser m (F Inlines)
doubleQuoted :: forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
doubleQuoted = ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
Bool -> OrgParser m ()
forall (m :: * -> *). PandocMonad m => Bool -> OrgParser m ()
guardOrSmartEnabled (Bool -> OrgParser m ())
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
-> OrgParser m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (ExportSettings -> Bool)
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) Bool
forall (m :: * -> *) a.
Monad m =>
(ExportSettings -> a) -> OrgParser m a
getExportSetting ExportSettings -> Bool
exportSmartQuotes
OrgParser m ()
forall st (m :: * -> *) s.
(HasLastStrPosition st, HasQuoteContext st m, Stream s m Char,
UpdateSourcePos s Char) =>
ParsecT s st m ()
doubleQuoteStart
Char -> OrgParser m Char
forall (m :: * -> *). PandocMonad m => Char -> OrgParser m Char
updatePositions Char
'"'
F Inlines
contents <- [F Inlines] -> F Inlines
forall a. Monoid a => [a] -> a
mconcat ([F Inlines] -> F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) [F Inlines]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ OrgParser m () -> OrgParser m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy OrgParser m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
doubleQuoteEnd OrgParser m ()
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b.
ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
-> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall (m :: * -> *). PandocMonad m => OrgParser m (F Inlines)
inline)
let doubleQuotedContent :: ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
doubleQuotedContent = QuoteContext
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s a.
QuoteContext
-> ParsecT s OrgParserState (ReaderT OrgParserLocal m) a
-> ParsecT s OrgParserState (ReaderT OrgParserLocal 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 OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ do
OrgParser m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m ()
doubleQuoteEnd
OrgParser m ()
forall (m :: * -> *). Monad m => OrgParser m ()
updateLastForbiddenCharPos
F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> (F Inlines -> F Inlines)
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inlines -> Inlines) -> F Inlines -> F Inlines
forall a b.
(a -> b) -> Future OrgParserState a -> Future OrgParserState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.doubleQuoted (F Inlines -> F Inlines)
-> (F Inlines -> F Inlines) -> F Inlines -> F Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. F Inlines -> F Inlines
forall s. Future s Inlines -> Future s Inlines
trimInlinesF (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ F Inlines
contents
let leftQuoteAndContent :: ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
leftQuoteAndContent = F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a.
a -> ParsecT Sources OrgParserState (ReaderT OrgParserLocal m) a
forall (m :: * -> *) a. Monad m => a -> m a
return (F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines))
-> F Inlines
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall a b. (a -> b) -> a -> b
$ Inlines -> F Inlines
forall a. a -> Future OrgParserState a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Inlines
B.str Text
"\8220") F Inlines -> F Inlines -> F Inlines
forall a. Semigroup a => a -> a -> a
<> F Inlines
contents
ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
doubleQuotedContent ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
-> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT
Sources OrgParserState (ReaderT OrgParserLocal m) (F Inlines)
leftQuoteAndContent