{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
module Text.Pandoc.Readers.LaTeX ( readLaTeX,
applyMacros,
rawLaTeXInline,
rawLaTeXBlock,
inlineCommand
) where
import Control.Applicative (many, optional, (<|>))
import Control.Monad
import Control.Monad.Except (throwError)
import Data.Containers.ListUtils (nubOrd)
import Data.Char (isDigit, isLetter, isAlphaNum, toUpper, chr)
import Data.Default
import Data.List (intercalate)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, maybeToList)
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import Data.Either (partitionEithers)
import Skylighting (defaultSyntaxMap)
import System.FilePath (addExtension, replaceExtension, takeExtension)
import Text.Collate.Lang (renderLang)
import Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocPure, PandocMonad (..), getResourcePath,
readFileFromDirs, report,
setResourcePath, getZonedTime)
import Data.Time (ZonedTime(..), LocalTime(..), showGregorian)
import Text.Pandoc.Error (PandocError (PandocParseError))
import Text.Pandoc.Highlighting (languagesByExtension)
import Text.Pandoc.ImageSize (numUnit, showFl)
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (blankline, many, mathDisplay, mathInline,
optional, space, spaces, withRaw, (<|>))
import Text.Pandoc.TeX (Tok (..), TokType (..))
import Text.Pandoc.Readers.LaTeX.Parsing
import Text.Pandoc.Readers.LaTeX.Citation (citationCommands, cites)
import Text.Pandoc.Readers.LaTeX.Math (dollarsMath, inlineEnvironments,
inlineEnvironment,
mathDisplay, mathInline,
newtheorem, theoremstyle, proof,
theoremEnvironment)
import Text.Pandoc.Readers.LaTeX.Table (tableEnvironments)
import Text.Pandoc.Readers.LaTeX.Macro (macroDef)
import Text.Pandoc.Readers.LaTeX.Lang (inlineLanguageCommands,
enquoteCommands,
babelLangToBCP47,
setDefaultLanguage)
import Text.Pandoc.Readers.LaTeX.SIunitx (siunitxCommands)
import Text.Pandoc.Readers.LaTeX.Inline (acronymCommands, refCommands,
nameCommands, charCommands,
accentCommands,
biblatexInlineCommands,
verbCommands, rawInlineOr,
listingsLanguage)
import Text.Pandoc.Shared
import Text.Pandoc.Walk
import Data.List.NonEmpty (nonEmpty)
readLaTeX :: (PandocMonad m, ToSources a)
=> ReaderOptions
-> a
-> m Pandoc
readLaTeX :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readLaTeX ReaderOptions
opts a
ltx = do
let sources :: Sources
sources = a -> Sources
forall a. ToSources a => a -> Sources
toSources a
ltx
Either ParseError Pandoc
parsed <- ParsecT TokStream LaTeXState m Pandoc
-> LaTeXState
-> String
-> TokStream
-> m (Either ParseError Pandoc)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> String -> s -> m (Either ParseError a)
runParserT ParsecT TokStream LaTeXState m Pandoc
forall (m :: * -> *). PandocMonad m => LP m Pandoc
parseLaTeX LaTeXState
forall a. Default a => a
def{ sOptions = opts } String
"source"
(Bool -> [Tok] -> TokStream
TokStream Bool
False (Sources -> [Tok]
tokenizeSources Sources
sources))
case Either ParseError Pandoc
parsed of
Right Pandoc
result -> Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
result
Left ParseError
e -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Sources -> ParseError -> PandocError
fromParsecError Sources
sources ParseError
e
parseLaTeX :: PandocMonad m => LP m Pandoc
parseLaTeX :: forall (m :: * -> *). PandocMonad m => LP m Pandoc
parseLaTeX = do
Blocks
bs <- LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
LaTeXState
st <- ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let meta :: Meta
meta = LaTeXState -> Meta
sMeta LaTeXState
st
let doc' :: Pandoc
doc' = Blocks -> Pandoc
doc Blocks
bs
let headerLevel :: Block -> [Int]
headerLevel (Header Int
n Attr
_ [Inline]
_) = [Int
n]
headerLevel Block
_ = []
let bottomLevel :: Int
bottomLevel = Int -> (NonEmpty Int -> Int) -> Maybe (NonEmpty Int) -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
1 NonEmpty Int -> Int
forall a. Ord a => NonEmpty a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum (Maybe (NonEmpty Int) -> Int) -> Maybe (NonEmpty Int) -> Int
forall a b. (a -> b) -> a -> b
$ [Int] -> Maybe (NonEmpty Int)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ([Int] -> Maybe (NonEmpty Int)) -> [Int] -> Maybe (NonEmpty Int)
forall a b. (a -> b) -> a -> b
$ (Block -> [Int]) -> Pandoc -> [Int]
forall c. Monoid c => (Block -> c) -> Pandoc -> c
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Block -> [Int]
headerLevel Pandoc
doc'
let adjustHeaders :: Int -> Block -> Block
adjustHeaders Int
m (Header Int
n Attr
attr [Inline]
ils) = Int -> Attr -> [Inline] -> Block
Header (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
m) Attr
attr [Inline]
ils
adjustHeaders Int
_ Block
x = Block
x
let (Pandoc Meta
_ [Block]
bs') =
(if Int
bottomLevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1
then (Block -> Block) -> Pandoc -> Pandoc
forall a b. Walkable a b => (a -> a) -> b -> b
walk (Int -> Block -> Block
adjustHeaders (Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
bottomLevel))
else Pandoc -> Pandoc
forall a. a -> a
id) (Pandoc -> Pandoc) -> Pandoc -> Pandoc
forall a b. (a -> b) -> a -> b
$
(Inline -> Inline) -> Pandoc -> Pandoc
forall a b. Walkable a b => (a -> a) -> b -> b
walk (Map Text [Inline] -> Inline -> Inline
resolveRefs (LaTeXState -> Map Text [Inline]
sLabels LaTeXState
st)) Pandoc
doc'
Pandoc -> LP m Pandoc
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> LP m Pandoc) -> Pandoc -> LP m Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc Meta
meta [Block]
bs'
resolveRefs :: M.Map Text [Inline] -> Inline -> Inline
resolveRefs :: Map Text [Inline] -> Inline -> Inline
resolveRefs Map Text [Inline]
labels x :: Inline
x@(Link (Text
ident,[Text]
classes,[(Text, Text)]
kvs) [Inline]
_ (Text, Text)
_) =
case ((Char -> Bool) -> Text -> Text
T.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'+') (Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"reference-type" [(Text, Text)]
kvs,
Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"reference" [(Text, Text)]
kvs) of
(Just Text
"ref", Just Text
lab) ->
case Text -> Map Text [Inline] -> Maybe [Inline]
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
lab Map Text [Inline]
labels of
Just [Inline]
txt -> Attr -> [Inline] -> (Text, Text) -> Inline
Link (Text
ident,[Text]
classes,[(Text, Text)]
kvs) [Inline]
txt (Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
lab, Text
"")
Maybe [Inline]
Nothing -> Inline
x
(Maybe Text, Maybe Text)
_ -> Inline
x
resolveRefs Map Text [Inline]
_ Inline
x = Inline
x
rawLaTeXBlock :: (PandocMonad m, HasMacros s, HasReaderOptions s)
=> ParsecT Sources s m Text
rawLaTeXBlock :: forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
ParsecT Sources s m Text
rawLaTeXBlock = do
ParsecT Sources s m Char -> ParsecT Sources s 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 s m Char -> ParsecT Sources s m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Sources s 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 s m Char
-> ParsecT Sources s m Char -> ParsecT Sources s m Char
forall a b.
ParsecT Sources s m a
-> ParsecT Sources s m b -> ParsecT Sources s m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources s m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter))
[Tok]
toks <- ParsecT Sources s m [Tok]
forall (m :: * -> *) s. PandocMonad m => ParsecT Sources s m [Tok]
getInputTokens
(Blocks, Text) -> Text
forall a b. (a, b) -> b
snd ((Blocks, Text) -> Text)
-> ParsecT Sources s m (Blocks, Text) -> ParsecT Sources s m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (
[Tok]
-> LP m Blocks -> LP m Blocks -> ParsecT Sources s m (Blocks, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s, Show a) =>
[Tok] -> LP m a -> LP m a -> ParsecT Sources s m (a, Text)
rawLaTeXParser [Tok]
toks
((Text -> Blocks) -> LP m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
(Text -> a) -> LP m a
macroDef (Blocks -> Text -> Blocks
forall a b. a -> b -> a
const Blocks
forall a. Monoid a => a
mempty) LP m Blocks -> LP m Blocks -> LP m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
do [ParsecT TokStream LaTeXState m Tok]
-> ParsecT TokStream LaTeXState m Tok
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice ((Text -> ParsecT TokStream LaTeXState m Tok)
-> [Text] -> [ParsecT TokStream LaTeXState m Tok]
forall a b. (a -> b) -> [a] -> [b]
map Text -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq
[Text
"include", Text
"input", Text
"subfile", Text
"usepackage"])
ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt
LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty) LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
ParsecT Sources s m (Blocks, Text)
-> ParsecT Sources s m (Blocks, Text)
-> ParsecT Sources s m (Blocks, Text)
forall a.
ParsecT Sources s m a
-> ParsecT Sources s m a -> ParsecT Sources s m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Tok]
-> LP m Blocks -> LP m Blocks -> ParsecT Sources s m (Blocks, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s, Show a) =>
[Tok] -> LP m a -> LP m a -> ParsecT Sources s m (a, Text)
rawLaTeXParser [Tok]
toks
(LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
environment LP m Blocks -> LP m Blocks -> LP m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blockCommand)
([Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT TokStream LaTeXState m [Blocks] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks -> ParsecT TokStream LaTeXState m [Blocks]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block LP m Blocks -> LP m Blocks -> LP m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
beginOrEndCommand)))
beginOrEndCommand :: PandocMonad m => LP m Blocks
beginOrEndCommand :: forall (m :: * -> *). PandocMonad m => LP m Blocks
beginOrEndCommand = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
Tok SourcePos
_ (CtrlSeq Text
name) Text
txt <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyControlSeq
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"begin" Bool -> Bool -> Bool
|| Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"end"
([Tok]
envname, [Tok]
rawargs) <- LP m [Tok] -> LP m ([Tok], [Tok])
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m (a, [Tok])
withRaw LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
if Text -> Map Text (LP PandocPure Inlines) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
M.member ([Tok] -> Text
untokenize [Tok]
envname)
(Map Text (LP PandocPure Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
inlineEnvironments :: M.Map Text (LP PandocPure Inlines))
then ParsecT TokStream LaTeXState m Blocks
forall a. ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
else Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT TokStream LaTeXState m Blocks)
-> Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Blocks
rawBlock Text
"latex"
(Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
rawargs)
rawLaTeXInline :: (PandocMonad m, HasMacros s, HasReaderOptions s)
=> ParsecT Sources s m Text
rawLaTeXInline :: forall (m :: * -> *) s.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
ParsecT Sources s m Text
rawLaTeXInline = do
ParsecT Sources s m Char -> ParsecT Sources s 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 s m Char -> ParsecT Sources s m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Sources s 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 s m Char
-> ParsecT Sources s m Char -> ParsecT Sources s m Char
forall a b.
ParsecT Sources s m a
-> ParsecT Sources s m b -> ParsecT Sources s m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources s m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter))
[Tok]
toks <- ParsecT Sources s m [Tok]
forall (m :: * -> *) s. PandocMonad m => ParsecT Sources s m [Tok]
getInputTokens
Text
raw <- (Inlines, Text) -> Text
forall a b. (a, b) -> b
snd ((Inlines, Text) -> Text)
-> ParsecT Sources s m (Inlines, Text) -> ParsecT Sources s m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
( [Tok]
-> LP m Inlines
-> LP m Inlines
-> ParsecT Sources s m (Inlines, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s, Show a) =>
[Tok] -> LP m a -> LP m a -> ParsecT Sources s m (a, Text)
rawLaTeXParser [Tok]
toks
(Inlines
forall a. Monoid a => a
mempty Inlines -> ParsecT TokStream LaTeXState m [Tok] -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"input" LP m Tok
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => LP m Text
rawopt ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced))
LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines
ParsecT Sources s m (Inlines, Text)
-> ParsecT Sources s m (Inlines, Text)
-> ParsecT Sources s m (Inlines, Text)
forall a.
ParsecT Sources s m a
-> ParsecT Sources s m a -> ParsecT Sources s m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Tok]
-> LP m Inlines
-> LP m Inlines
-> ParsecT Sources s m (Inlines, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s, Show a) =>
[Tok] -> LP m a -> LP m a -> ParsecT Sources s m (a, Text)
rawLaTeXParser [Tok]
toks (LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineEnvironment LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineCommand')
LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines
)
String
finalbraces <- [String] -> String
forall a. Monoid a => [a] -> a
mconcat ([String] -> String)
-> ParsecT Sources s m [String] -> ParsecT Sources s m String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources s m String -> ParsecT Sources s m [String]
forall a. ParsecT Sources s m a -> ParsecT Sources s m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT Sources s m String -> ParsecT Sources s m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (String -> ParsecT Sources s m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{}"))
Text -> ParsecT Sources s m Text
forall a. a -> ParsecT Sources s m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources s m Text)
-> Text -> ParsecT Sources s m Text
forall a b. (a -> b) -> a -> b
$ Text
raw Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
finalbraces
inlineCommand :: PandocMonad m => ParsecT Sources ParserState m Inlines
inlineCommand :: forall (m :: * -> *).
PandocMonad m =>
ParsecT Sources ParserState m Inlines
inlineCommand = do
ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall a b.
ParsecT Sources ParserState m a
-> ParsecT Sources ParserState m b
-> ParsecT Sources ParserState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
letter))
[Tok]
toks <- ParsecT Sources ParserState m [Tok]
forall (m :: * -> *) s. PandocMonad m => ParsecT Sources s m [Tok]
getInputTokens
(Inlines, Text) -> Inlines
forall a b. (a, b) -> a
fst ((Inlines, Text) -> Inlines)
-> ParsecT Sources ParserState m (Inlines, Text)
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Tok]
-> LP m Inlines
-> LP m Inlines
-> ParsecT Sources ParserState m (Inlines, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s, Show a) =>
[Tok] -> LP m a -> LP m a -> ParsecT Sources s m (a, Text)
rawLaTeXParser [Tok]
toks (LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineEnvironment LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineCommand')
LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines
inlineGroup :: PandocMonad m => LP m Inlines
inlineGroup :: forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineGroup = do
Inlines
ils <- LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
if Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
ils
then Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
else Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith Attr
nullAttr Inlines
ils
doLHSverb :: PandocMonad m => LP m Inlines
doLHSverb :: forall (m :: * -> *). PandocMonad m => LP m Inlines
doLHSverb =
Attr -> Text -> Inlines
codeWith (Text
"",[Text
"haskell"],[]) (Text -> Inlines) -> ([Tok] -> Text) -> [Tok] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize
([Tok] -> Inlines)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ((Tok -> Bool) -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => (Tok -> Bool) -> LP m Tok
satisfyTok (Bool -> Bool
not (Bool -> Bool) -> (Tok -> Bool) -> Tok -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tok -> Bool
isNewlineTok)) (Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'|')
mkImage :: PandocMonad m => [(Text, Text)] -> Text -> LP m Inlines
mkImage :: forall (m :: * -> *).
PandocMonad m =>
[(Text, Text)] -> Text -> LP m Inlines
mkImage [(Text, Text)]
options (Text -> String
T.unpack -> String
src) = do
let replaceRelative :: (a, Text) -> (a, Text)
replaceRelative (a
k,Text
v) =
case Text -> Maybe (Double, Text)
numUnit Text
v of
Just (Double
num, Text
"\\textwidth") -> (a
k, Double -> Text
forall a. RealFloat a => a -> Text
showFl (Double
num Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
100) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"%")
Just (Double
num, Text
"\\linewidth") -> (a
k, Double -> Text
forall a. RealFloat a => a -> Text
showFl (Double
num Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
100) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"%")
Just (Double
num, Text
"\\textheight") -> (a
k, Double -> Text
forall a. RealFloat a => a -> Text
showFl (Double
num Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
100) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"%")
Maybe (Double, Text)
_ -> (a
k, Text
v)
let kvs :: [(Text, Text)]
kvs = ((Text, Text) -> (Text, Text)) -> [(Text, Text)] -> [(Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Text) -> (Text, Text)
forall {a}. (a, Text) -> (a, Text)
replaceRelative
([(Text, Text)] -> [(Text, Text)])
-> [(Text, Text)] -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> Bool) -> [(Text, Text)] -> [(Text, Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Text
k,Text
_) -> Text
k Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"width", Text
"height"]) [(Text, Text)]
options
let attr :: (Text, [a], [(Text, Text)])
attr = (Text
"",[], [(Text, Text)]
kvs)
let alt :: Inlines
alt = Inlines -> (Text -> Inlines) -> Maybe Text -> Inlines
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Text -> Inlines
str Text
"image") Text -> Inlines
str (Maybe Text -> Inlines) -> Maybe Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"alt" [(Text, Text)]
options
Text
defaultExt <- (ReaderOptions -> Text) -> ParsecT TokStream LaTeXState m Text
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 LaTeXState m b
getOption ReaderOptions -> Text
readerDefaultImageExtension
let exts' :: [String]
exts' = [String
".pdf", String
".png", String
".jpg", String
".mps", String
".jpeg", String
".jbig2", String
".jb2"]
let exts :: [String]
exts = [String]
exts' [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper) [String]
exts'
let findFile :: String -> [String] -> m String
findFile String
s [] = String -> m String
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return String
s
findFile String
s (String
e:[String]
es) = do
let s' :: String
s' = String -> String -> String
addExtension String
s String
e
Bool
exists <- String -> m Bool
forall (m :: * -> *). PandocMonad m => String -> m Bool
fileExists String
s'
if Bool
exists
then String -> m String
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return String
s'
else String -> [String] -> m String
findFile String
s [String]
es
String
src' <- case String -> String
takeExtension String
src of
String
"" | Bool -> Bool
not (Text -> Bool
T.null Text
defaultExt) -> String -> ParsecT TokStream LaTeXState m String
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ParsecT TokStream LaTeXState m String)
-> String -> ParsecT TokStream LaTeXState m String
forall a b. (a -> b) -> a -> b
$ String -> String -> String
addExtension String
src (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
defaultExt
| Bool
otherwise -> String -> [String] -> ParsecT TokStream LaTeXState m String
forall {m :: * -> *}.
PandocMonad m =>
String -> [String] -> m String
findFile String
src [String]
exts
String
_ -> String -> ParsecT TokStream LaTeXState m String
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return String
src
Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
imageWith Attr
forall {a}. (Text, [a], [(Text, Text)])
attr (String -> Text
T.pack String
src') Text
"" Inlines
alt
removeDoubleQuotes :: Text -> Text
removeDoubleQuotes :: Text -> Text
removeDoubleQuotes Text
t =
Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
Data.Maybe.fromMaybe Text
t (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Text
T.stripPrefix Text
"\"" Text
t Maybe Text -> (Text -> Maybe Text) -> Maybe Text
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Text -> Maybe Text
T.stripSuffix Text
"\""
doubleQuote :: PandocMonad m => LP m Inlines
doubleQuote :: forall (m :: * -> *). PandocMonad m => LP m Inlines
doubleQuote =
(Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
quoted' Inlines -> Inlines
doubleQuoted (LP m [Tok] -> LP m [Tok]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m [Tok] -> LP m [Tok]) -> LP m [Tok] -> LP m [Tok]
forall a b. (a -> b) -> a -> b
$ Int -> ParsecT TokStream LaTeXState m Tok -> LP m [Tok]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
2 (ParsecT TokStream LaTeXState m Tok -> LP m [Tok])
-> ParsecT TokStream LaTeXState m Tok -> LP m [Tok]
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'`')
(LP m [Tok] -> LP m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (LP m [Tok] -> LP m ()) -> LP m [Tok] -> LP m ()
forall a b. (a -> b) -> a -> b
$ LP m [Tok] -> LP m [Tok]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m [Tok] -> LP m [Tok]) -> LP m [Tok] -> LP m [Tok]
forall a b. (a -> b) -> a -> b
$ Int -> ParsecT TokStream LaTeXState m Tok -> LP m [Tok]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
2 (ParsecT TokStream LaTeXState m Tok -> LP m [Tok])
-> ParsecT TokStream LaTeXState m Tok -> LP m [Tok]
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\'')
LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
quoted' Inlines -> Inlines
doubleQuoted ((Tok -> [Tok] -> [Tok]
forall a. a -> [a] -> [a]
:[]) (Tok -> [Tok]) -> ParsecT TokStream LaTeXState m Tok -> LP m [Tok]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'“') (ParsecT TokStream LaTeXState m Tok -> LP m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT TokStream LaTeXState m Tok -> LP m ())
-> ParsecT TokStream LaTeXState m Tok -> LP m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'”')
LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
quoted' Inlines -> Inlines
doubleQuoted (LP m [Tok] -> LP m [Tok]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m [Tok] -> LP m [Tok]) -> LP m [Tok] -> LP m [Tok]
forall a b. (a -> b) -> a -> b
$ [ParsecT TokStream LaTeXState m Tok] -> LP m [Tok]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'"', Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'`'])
(LP m [Tok] -> LP m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (LP m [Tok] -> LP m ()) -> LP m [Tok] -> LP m ()
forall a b. (a -> b) -> a -> b
$ LP m [Tok] -> LP m [Tok]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m [Tok] -> LP m [Tok]) -> LP m [Tok] -> LP m [Tok]
forall a b. (a -> b) -> a -> b
$ [ParsecT TokStream LaTeXState m Tok] -> LP m [Tok]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'"', Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\''])
singleQuote :: PandocMonad m => LP m Inlines
singleQuote :: forall (m :: * -> *). PandocMonad m => LP m Inlines
singleQuote =
(Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
quoted' Inlines -> Inlines
singleQuoted ((Tok -> [Tok] -> [Tok]
forall a. a -> [a] -> [a]
:[]) (Tok -> [Tok]) -> ParsecT TokStream LaTeXState m Tok -> LP m [Tok]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'`')
(LP m () -> LP m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m () -> LP m ()) -> LP m () -> LP m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\'' ParsecT TokStream LaTeXState m Tok -> LP m () -> LP m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT TokStream LaTeXState m Tok -> LP m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ((Tok -> Bool) -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => (Tok -> Bool) -> LP m Tok
satisfyTok Tok -> Bool
startsWithLetter))
LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
quoted' Inlines -> Inlines
singleQuoted ((Tok -> [Tok] -> [Tok]
forall a. a -> [a] -> [a]
:[]) (Tok -> [Tok]) -> ParsecT TokStream LaTeXState m Tok -> LP m [Tok]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'‘')
(LP m () -> LP m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m () -> LP m ()) -> LP m () -> LP m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'’' ParsecT TokStream LaTeXState m Tok -> LP m () -> LP m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
ParsecT TokStream LaTeXState m Tok -> LP m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ((Tok -> Bool) -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => (Tok -> Bool) -> LP m Tok
satisfyTok Tok -> Bool
startsWithLetter))
where startsWithLetter :: Tok -> Bool
startsWithLetter (Tok SourcePos
_ TokType
Word Text
t) =
case Text -> Maybe (Char, Text)
T.uncons Text
t of
Just (Char
c, Text
_) | Char -> Bool
isLetter Char
c -> Bool
True
Maybe (Char, Text)
_ -> Bool
False
startsWithLetter Tok
_ = Bool
False
quoted' :: PandocMonad m
=> (Inlines -> Inlines)
-> LP m [Tok]
-> LP m ()
-> LP m Inlines
quoted' :: forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Inlines) -> LP m [Tok] -> LP m () -> LP m Inlines
quoted' Inlines -> Inlines
f LP m [Tok]
starter LP m ()
ender = do
Text
startchs <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> LP m [Tok] -> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m [Tok]
starter
Bool
smart <- Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_smart (Extensions -> Bool)
-> ParsecT TokStream LaTeXState m Extensions
-> ParsecT TokStream LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ReaderOptions -> Extensions)
-> ParsecT TokStream LaTeXState 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 LaTeXState m b
getOption ReaderOptions -> Extensions
readerExtensions
if Bool
smart
then do
[Inlines]
ils <- LP m Inlines -> ParsecT TokStream LaTeXState m [Inlines]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (LP m () -> LP m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy LP m ()
ender LP m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline)
(LP m ()
ender LP m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> Inlines
f ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat [Inlines]
ils))) LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat [Inlines]
ils) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Text -> LP m Inlines
forall (m :: * -> *). Text -> LP m Inlines
lit (case Text
startchs of
Text
"``" -> Text
"“"
Text
"`" -> Text
"‘"
Text
cs -> Text
cs)
else Text -> LP m Inlines
forall (m :: * -> *). Text -> LP m Inlines
lit Text
startchs
lit :: Text -> LP m Inlines
lit :: forall (m :: * -> *). Text -> LP m Inlines
lit = Inlines -> ParsecT TokStream LaTeXState m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ParsecT TokStream LaTeXState m Inlines)
-> (Text -> Inlines)
-> Text
-> ParsecT TokStream LaTeXState m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
str
blockquote :: PandocMonad m => Bool -> Maybe Text -> LP m Blocks
blockquote :: forall (m :: * -> *).
PandocMonad m =>
Bool -> Maybe Text -> LP m Blocks
blockquote Bool
cvariant Maybe Text
mblang = do
Blocks
citepar <- if Bool
cvariant
then (\[Citation]
xs -> Inlines -> Blocks
para ([Citation] -> Inlines -> Inlines
cite [Citation]
xs Inlines
forall a. Monoid a => a
mempty))
([Citation] -> Blocks)
-> ParsecT TokStream LaTeXState m [Citation] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
-> CitationMode
-> Bool
-> ParsecT TokStream LaTeXState m [Citation]
forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> CitationMode -> Bool -> LP m [Citation]
cites LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline CitationMode
NormalCitation Bool
False
else Blocks -> LP m Blocks -> LP m Blocks
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Blocks
forall a. Monoid a => a
mempty (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
para (Inlines -> Blocks) -> LP m Inlines -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
bracketed LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
let lang :: Maybe Lang
lang = Maybe Text
mblang Maybe Text -> (Text -> Maybe Lang) -> Maybe Lang
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Lang
babelLangToBCP47
let langdiv :: Blocks -> Blocks
langdiv = case Maybe Lang
lang of
Maybe Lang
Nothing -> Blocks -> Blocks
forall a. a -> a
id
Just Lang
l -> Attr -> Blocks -> Blocks
divWith (Text
"",[],[(Text
"lang", Lang -> Text
renderLang Lang
l)])
Inlines
_closingPunct <- Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Inlines
forall a. Monoid a => a
mempty (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
bracketed LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
Blocks
bs <- LP m Blocks -> LP m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m (Maybe Tok)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m (Maybe Tok))
-> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m (Maybe Tok)
forall a b. (a -> b) -> a -> b
$ String -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => String -> LP m Tok
symbolIn (String
".:;?!" :: [Char])
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks
blockQuote (Blocks -> Blocks) -> (Blocks -> Blocks) -> Blocks -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Blocks
langdiv (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ (Blocks
bs Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
citepar)
inlineCommand' :: PandocMonad m => LP m Inlines
inlineCommand' :: forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineCommand' = ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines)
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall a b. (a -> b) -> a -> b
$ do
Tok SourcePos
_ (CtrlSeq Text
name) Text
cmd <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyControlSeq
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"begin" Bool -> Bool -> Bool
&& Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"end" Bool -> Bool -> Bool
&& Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"and"
Text
star <- if (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isAlphaNum Text
name
then Text
-> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState 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
"" (Text
"*" Text -> LP m Tok -> ParsecT TokStream LaTeXState m Text
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'*' ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Text
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp)
else Text -> ParsecT TokStream LaTeXState m Text
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
""
Text
overlay <- Text
-> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => LP m Text
overlaySpecification
let name' :: Text
name' = Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
star Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
overlay
let names :: [Text]
names = [Text] -> [Text]
forall a. Ord a => [a] -> [a]
nubOrd [Text
name', Text
name]
let raw :: ParsecT TokStream LaTeXState m Inlines
raw = do
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> Bool
isInlineCommand Text
name Bool -> Bool -> Bool
|| Bool -> Bool
not (Text -> Bool
isBlockCommand Text
name)
Text
rawcommand <- Text -> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> Text -> LP m Text
getRawCommand Text
name (Text
cmd Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
star)
(Extension -> ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_tex ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT TokStream LaTeXState m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Inlines
rawInline Text
"latex" Text
rawcommand))
ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> ParsecT TokStream LaTeXState m Inlines
forall a (m :: * -> *) s u.
(Monoid a, PandocMonad m) =>
Text -> ParsecT s u m a
ignore Text
rawcommand
ParsecT TokStream LaTeXState m Inlines
-> [Text]
-> Map Text (ParsecT TokStream LaTeXState m Inlines)
-> ParsecT TokStream LaTeXState m Inlines
forall k v. Ord k => v -> [k] -> Map k v -> v
lookupListDefault ParsecT TokStream LaTeXState m Inlines
raw [Text]
names Map Text (ParsecT TokStream LaTeXState m Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
inlineCommands
tok :: PandocMonad m => LP m Inlines
tok :: forall (m :: * -> *). PandocMonad m => LP m Inlines
tok = LP m Inlines -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m Inlines
tokWith LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
unescapeURL :: Text -> Text
unescapeURL :: Text -> Text
unescapeURL = [Text] -> Text
T.concat ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
go ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
"\\"
where
isEscapable :: Char -> Bool
isEscapable Char
c = (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c) Text
"#$%&~_^\\{}"
go :: [Text] -> [Text]
go (Text
x:[Text]
xs) = Text
x Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
unescapeInterior [Text]
xs
go [] = []
unescapeInterior :: Text -> Text
unescapeInterior Text
t
| Just (Char
c, Text
_) <- Text -> Maybe (Char, Text)
T.uncons Text
t
, Char -> Bool
isEscapable Char
c = Text
t
| Bool
otherwise = Text
"\\" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
inlineCommands :: PandocMonad m => M.Map Text (LP m Inlines)
inlineCommands :: forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
inlineCommands = [Map Text (LP m Inlines)] -> Map Text (LP m Inlines)
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
M.unions
[ LP m Inlines -> Map Text (LP m Inlines)
forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Map Text (LP m Inlines)
accentCommands LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
, LP m Inlines -> Map Text (LP m Inlines)
forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Map Text (LP m Inlines)
citationCommands LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
, LP m Inlines -> Map Text (LP m Inlines)
forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Map Text (LP m Inlines)
siunitxCommands LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
, Map Text (LP m Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
acronymCommands
, Map Text (LP m Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
refCommands
, Map Text (LP m Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
nameCommands
, Map Text (LP m Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
verbCommands
, Map Text (LP m Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
charCommands
, LP m Inlines -> Map Text (LP m Inlines)
forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Map Text (LP m Inlines)
enquoteCommands LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
, LP m Inlines -> Map Text (LP m Inlines)
forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Map Text (LP m Inlines)
inlineLanguageCommands LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
, LP m Inlines -> Map Text (LP m Inlines)
forall (m :: * -> *).
PandocMonad m =>
LP m Inlines -> Map Text (LP m Inlines)
biblatexInlineCommands LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
, Map Text (LP m Inlines)
rest ]
where
rest :: Map Text (LP m Inlines)
rest = [(Text, LP m Inlines)] -> Map Text (LP m Inlines)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"emph", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
emph (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textit", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
emph (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textsl", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
emph (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textsc", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
smallcaps (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textsf", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"sans-serif"],[])) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textmd", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"medium"],[])) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textrm", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"roman"],[])) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textup", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"upright"],[])) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"texttt", Attr -> Inlines -> Inlines
formatCode Attr
nullAttr (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"alert", LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts LP m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"alert"],[]) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textsuperscript", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
superscript (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textsubscript", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
subscript (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textbf", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
strong (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textnormal", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"nodecor"],[])) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"underline", Inlines -> Inlines
underline (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"mbox", Text -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Inlines -> LP m Inlines
rawInlineOr Text
"mbox" (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
processHBox (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"hbox", Text -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Inlines -> LP m Inlines
rawInlineOr Text
"hbox" (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
processHBox (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"vbox", Text -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Inlines -> LP m Inlines
rawInlineOr Text
"vbox" LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"lettrine", Text -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Inlines -> LP m Inlines
rawInlineOr Text
"lettrine" LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
lettrine)
, (Text
"(", Text -> Inlines
mathInline (Text -> Inlines) -> ([Tok] -> Text) -> [Tok] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Inlines)
-> ParsecT TokStream LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Text -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
")"))
, (Text
"[", Text -> Inlines
mathDisplay (Text -> Inlines) -> ([Tok] -> Text) -> [Tok] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Inlines)
-> ParsecT TokStream LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Text -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"]"))
, (Text
"ensuremath", Text -> Inlines
mathInline (Text -> Inlines) -> ([Tok] -> Text) -> [Tok] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Inlines)
-> ParsecT TokStream LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced)
, (Text
"texorpdfstring", Inlines -> Inlines -> Inlines
forall a b. a -> b -> a
const (Inlines -> Inlines -> Inlines)
-> LP m Inlines
-> ParsecT TokStream LaTeXState m (Inlines -> Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok ParsecT TokStream LaTeXState m (Inlines -> Inlines)
-> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m (a -> b)
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"em", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
emph (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"it", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
emph (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"sl", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
emph (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"bf", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
strong (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"tt", Attr -> Inlines -> Inlines
formatCode Attr
nullAttr (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"rm", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"itshape", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
emph (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"slshape", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
emph (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"scshape", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
smallcaps (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"bfseries", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
strong (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines)
, (Text
"MakeUppercase", Inlines -> Inlines
makeUppercase (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"MakeTextUppercase", Inlines -> Inlines
makeUppercase (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"uppercase", Inlines -> Inlines
makeUppercase (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"MakeLowercase", Inlines -> Inlines
makeLowercase (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"MakeTextLowercase", Inlines -> Inlines
makeLowercase (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"lowercase", Inlines -> Inlines
makeLowercase (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"thanks", LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts LP m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> Inlines
note (Blocks -> Inlines)
-> ParsecT TokStream LaTeXState m Blocks -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block)
, (Text
"footnote", LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts LP m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
footnote)
, (Text
"passthrough", Inlines -> Inlines
fixPassthroughEscapes (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"includegraphics", do [(Text, Text)]
options <- [(Text, Text)]
-> ParsecT TokStream LaTeXState m [(Text, Text)]
-> ParsecT TokStream LaTeXState 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 TokStream LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
[Tok]
src <- ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
[(Text, Text)] -> Text -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
[(Text, Text)] -> Text -> LP m Inlines
mkImage [(Text, Text)]
options (Text -> LP m Inlines) -> (Text -> Text) -> Text -> LP m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text
unescapeURL (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text
removeDoubleQuotes (Text -> LP m Inlines) -> Text -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ [Tok] -> Text
untokenize [Tok]
src)
, (Text
"includesvg", do [(Text, Text)]
options <- [(Text, Text)]
-> ParsecT TokStream LaTeXState m [(Text, Text)]
-> ParsecT TokStream LaTeXState 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 TokStream LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
[Tok]
src <- ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
[(Text, Text)] -> Text -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
[(Text, Text)] -> Text -> LP m Inlines
mkImage [(Text, Text)]
options (Text -> LP m Inlines) -> (Text -> Text) -> Text -> LP m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text
unescapeURL (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text
removeDoubleQuotes (Text -> LP m Inlines) -> Text -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ [Tok] -> Text
untokenize [Tok]
src)
, (Text
"url", (\Text
url -> Attr -> Text -> Text -> Inlines -> Inlines
linkWith (Text
"",[Text
"uri"],[]) Text
url Text
"" (Text -> Inlines
str Text
url))
(Text -> Inlines) -> ([Tok] -> Text) -> [Tok] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
unescapeURL (Text -> Text) -> ([Tok] -> Text) -> [Tok] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Inlines)
-> ParsecT TokStream LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl)
, (Text
"nolinkurl", Text -> Inlines
code (Text -> Inlines) -> ([Tok] -> Text) -> [Tok] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
unescapeURL (Text -> Text) -> ([Tok] -> Text) -> [Tok] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Inlines)
-> ParsecT TokStream LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl)
, (Text
"href", do [Tok]
url <- ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp
Text -> Text -> Inlines -> Inlines
link (Text -> Text
unescapeURL (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Tok] -> Text
untokenize [Tok]
url) Text
"" (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"hyperlink", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
hyperlink)
, (Text
"hyperref", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
hyperref)
, (Text
"hypertarget", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
hypertargetInline)
, (Text
"nohyphens", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textnhtt", Attr -> Inlines -> Inlines
formatCode Attr
nullAttr (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"nhttfamily", Attr -> Inlines -> Inlines
formatCode Attr
nullAttr (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"textcolor", Text -> LP m Inlines
forall (m :: * -> *). PandocMonad m => Text -> LP m Inlines
coloredInline Text
"color")
, (Text
"colorbox", Text -> LP m Inlines
forall (m :: * -> *). PandocMonad m => Text -> LP m Inlines
coloredInline Text
"background-color")
, (Text
"ifstrequal", LP m Inlines
forall (m :: * -> *) a. (PandocMonad m, Monoid a) => LP m a
ifstrequal)
, (Text
"newtoggle", ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok]
-> ([Tok] -> LP m Inlines) -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Tok] -> LP m Inlines
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
[Tok] -> LP m a
newToggle)
, (Text
"toggletrue", ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok]
-> ([Tok] -> LP m Inlines) -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> [Tok] -> LP m Inlines
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Bool -> [Tok] -> LP m a
setToggle Bool
True)
, (Text
"togglefalse", ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok]
-> ([Tok] -> LP m Inlines) -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> [Tok] -> LP m Inlines
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Bool -> [Tok] -> LP m a
setToggle Bool
False)
, (Text
"iftoggle", LP m Inlines -> LP m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
ifToggle LP m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline)
, (Text
"input", Text -> LP m Inlines -> LP m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Inlines -> LP m Inlines
rawInlineOr Text
"input" (LP m Inlines -> LP m Inlines) -> LP m Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> LP m Inlines
forall (m :: * -> *) a. (PandocMonad m, Monoid a) => Text -> LP m a
include Text
"input")
, (Text
"st", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
strikeout (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"ul", Inlines -> Inlines
underline (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"hl", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"mark"],[])) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"sout", (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
strikeout (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"uline", Inlines -> Inlines
underline (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
, (Text
"ifdim", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
ifdim)
, (Text
"today", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
today)
]
today :: PandocMonad m => LP m Inlines
today :: forall (m :: * -> *). PandocMonad m => LP m Inlines
today =
Text -> Inlines
text (Text -> Inlines) -> (ZonedTime -> Text) -> ZonedTime -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (ZonedTime -> String) -> ZonedTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> String
showGregorian (Day -> String) -> (ZonedTime -> Day) -> ZonedTime -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LocalTime -> Day
localDay (LocalTime -> Day) -> (ZonedTime -> LocalTime) -> ZonedTime -> Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZonedTime -> LocalTime
zonedTimeToLocalTime
(ZonedTime -> Inlines)
-> ParsecT TokStream LaTeXState m ZonedTime
-> ParsecT TokStream LaTeXState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m ZonedTime
forall (m :: * -> *). PandocMonad m => m ZonedTime
getZonedTime
footnote :: PandocMonad m => LP m Inlines
= do
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sLastNoteNum = sLastNoteNum st + 1 }
Blocks
contents <- LP m Blocks -> LP m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block LP m Blocks -> (Blocks -> LP m Blocks) -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Inline -> ParsecT TokStream LaTeXState m Inline)
-> Blocks -> LP m Blocks
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
forall (m :: * -> *).
(Monad m, Applicative m, Functor m) =>
(Inline -> m Inline) -> Blocks -> m Blocks
walkM Inline -> ParsecT TokStream LaTeXState m Inline
forall (m :: * -> *). PandocMonad m => Inline -> LP m Inline
resolveNoteLabel
Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Blocks -> Inlines
note Blocks
contents
resolveNoteLabel :: PandocMonad m => Inline -> LP m Inline
resolveNoteLabel :: forall (m :: * -> *). PandocMonad m => Inline -> LP m Inline
resolveNoteLabel (Span (Text
_,[Text]
cls,[(Text, Text)]
kvs) [Inline]
_)
| Just Text
lab <- Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"label" [(Text, Text)]
kvs = do
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{
sLabels = M.insert lab (toList . text . tshow $ sLastNoteNum st)
$ sLabels st }
Inline -> LP m Inline
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inline -> LP m Inline) -> Inline -> LP m Inline
forall a b. (a -> b) -> a -> b
$ Attr -> [Inline] -> Inline
Span (Text
lab,[Text]
cls,[(Text, Text)]
kvs) []
resolveNoteLabel Inline
il = Inline -> LP m Inline
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
il
lettrine :: PandocMonad m => LP m Inlines
lettrine :: forall (m :: * -> *). PandocMonad m => LP m Inlines
lettrine = do
ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => LP m Text
rawopt
Inlines
x <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
Inlines
y <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces (Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"lettrine"],[])) Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines -> Inlines
smallcaps Inlines
y
ifdim :: PandocMonad m => LP m Inlines
ifdim :: forall (m :: * -> *). PandocMonad m => LP m Inlines
ifdim = do
[Tok]
contents <- ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Text -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"fi")
Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines
rawInline Text
"latex" (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
"\\ifdim" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\\fi"
makeUppercase :: Inlines -> Inlines
makeUppercase :: Inlines -> Inlines
makeUppercase = [Inline] -> Inlines
forall a. [a] -> Many a
fromList ([Inline] -> Inlines)
-> (Inlines -> [Inline]) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Inline) -> [Inline] -> [Inline]
forall a b. Walkable a b => (a -> a) -> b -> b
walk ((Text -> Text) -> Inline -> Inline
alterStr Text -> Text
T.toUpper) ([Inline] -> [Inline])
-> (Inlines -> [Inline]) -> Inlines -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList
makeLowercase :: Inlines -> Inlines
makeLowercase :: Inlines -> Inlines
makeLowercase = [Inline] -> Inlines
forall a. [a] -> Many a
fromList ([Inline] -> Inlines)
-> (Inlines -> [Inline]) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Inline) -> [Inline] -> [Inline]
forall a b. Walkable a b => (a -> a) -> b -> b
walk ((Text -> Text) -> Inline -> Inline
alterStr Text -> Text
T.toLower) ([Inline] -> [Inline])
-> (Inlines -> [Inline]) -> Inlines -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList
alterStr :: (Text -> Text) -> Inline -> Inline
alterStr :: (Text -> Text) -> Inline -> Inline
alterStr Text -> Text
f (Str Text
xs) = Text -> Inline
Str (Text -> Text
f Text
xs)
alterStr Text -> Text
_ Inline
x = Inline
x
fixPassthroughEscapes :: Inlines -> Inlines
fixPassthroughEscapes :: Inlines -> Inlines
fixPassthroughEscapes = (Inline -> Inline) -> Inlines -> Inlines
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
go
where
go :: Inline -> Inline
go (Code Attr
attr Text
txt) = Attr -> Text -> Inline
Code Attr
attr (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> String
unescapePassthrough (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
txt)
go Inline
x = Inline
x
unescapePassthrough :: String -> String
unescapePassthrough [] = []
unescapePassthrough (Char
'\\':Char
c:String
cs)
| Char
c Char -> String -> 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
c Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
unescapePassthrough String
cs
unescapePassthrough (Char
c:String
cs) = Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
unescapePassthrough String
cs
hyperlink :: PandocMonad m => LP m Inlines
hyperlink :: forall (m :: * -> *). PandocMonad m => LP m Inlines
hyperlink = ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines)
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall a b. (a -> b) -> a -> b
$ do
Text
src <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Inlines
lab <- ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
Inlines -> ParsecT TokStream LaTeXState m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT TokStream LaTeXState m Inlines)
-> Inlines -> ParsecT TokStream LaTeXState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
link (Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
src) Text
"" Inlines
lab
hyperref :: PandocMonad m => LP m Inlines
hyperref :: forall (m :: * -> *). PandocMonad m => LP m Inlines
hyperref = ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines)
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall a b. (a -> b) -> a -> b
$ do
Text
url <- ((Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> ([Tok] -> Text) -> [Tok] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp LP m ()
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracketedToks ParsecT TokStream LaTeXState m [Tok]
-> LP m () -> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp))
ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m Text
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl)
Text -> Text -> Inlines -> Inlines
link Text
url Text
"" (Inlines -> Inlines)
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
hypertargetBlock :: PandocMonad m => LP m Blocks
hypertargetBlock :: forall (m :: * -> *). PandocMonad m => LP m Blocks
hypertargetBlock = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
Text
ref <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Blocks
bs <- ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
case Blocks -> [Block]
forall a. Many a -> [a]
toList Blocks
bs of
[Header Int
1 (Text
ident,[Text]
_,[(Text, Text)]
_) [Inline]
_] | Text
ident Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
ref -> Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
bs
[Block]
_ -> Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT TokStream LaTeXState m Blocks)
-> Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
divWith (Text
ref, [], []) Blocks
bs
hypertargetInline :: PandocMonad m => LP m Inlines
hypertargetInline :: forall (m :: * -> *). PandocMonad m => LP m Inlines
hypertargetInline = ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines)
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall a b. (a -> b) -> a -> b
$ do
Text
ref <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Inlines
ils <- ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
Inlines -> ParsecT TokStream LaTeXState m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT TokStream LaTeXState m Inlines)
-> Inlines -> ParsecT TokStream LaTeXState m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith (Text
ref, [], []) Inlines
ils
newToggle :: (Monoid a, PandocMonad m) => [Tok] -> LP m a
newToggle :: forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
[Tok] -> LP m a
newToggle [Tok]
name = do
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st ->
LaTeXState
st{ sToggles = M.insert (untokenize name) False (sToggles st) }
a -> LP m a
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty
setToggle :: (Monoid a, PandocMonad m) => Bool -> [Tok] -> LP m a
setToggle :: forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Bool -> [Tok] -> LP m a
setToggle Bool
on [Tok]
name = do
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st ->
LaTeXState
st{ sToggles = M.adjust (const on) (untokenize name) (sToggles st) }
a -> LP m a
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty
ifToggle :: PandocMonad m => LP m ()
ifToggle :: forall (m :: * -> *). PandocMonad m => LP m ()
ifToggle = do
[Tok]
name <- LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
[Tok]
yes <- LP m [Tok] -> LP m [Tok]
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m a
withVerbatimMode LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
[Tok]
no <- LP m [Tok] -> LP m [Tok]
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m a
withVerbatimMode LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Map Text Bool
toggles <- LaTeXState -> Map Text Bool
sToggles (LaTeXState -> Map Text Bool)
-> ParsecT TokStream LaTeXState m LaTeXState
-> ParsecT TokStream LaTeXState m (Map Text Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
TokStream Bool
_ [Tok]
inp <- ParsecT TokStream LaTeXState m TokStream
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
let name' :: Text
name' = [Tok] -> Text
untokenize [Tok]
name
case Text -> Map Text Bool -> Maybe Bool
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
name' Map Text Bool
toggles of
Just Bool
True -> TokStream -> LP m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput (TokStream -> LP m ()) -> TokStream -> LP m ()
forall a b. (a -> b) -> a -> b
$ Bool -> [Tok] -> TokStream
TokStream Bool
False ([Tok]
yes [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++ [Tok]
inp)
Just Bool
False -> TokStream -> LP m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput (TokStream -> LP m ()) -> TokStream -> LP m ()
forall a b. (a -> b) -> a -> b
$ Bool -> [Tok] -> TokStream
TokStream Bool
False ([Tok]
no [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++ [Tok]
inp)
Maybe Bool
Nothing -> do
SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
LogMessage -> LP m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> LP m ()) -> LogMessage -> LP m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
UndefinedToggle Text
name' SourcePos
pos
() -> LP m ()
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
ifstrequal :: (PandocMonad m, Monoid a) => LP m a
ifstrequal :: forall (m :: * -> *) a. (PandocMonad m, Monoid a) => LP m a
ifstrequal = do
Inlines
str1 <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
Inlines
str2 <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
[Tok]
ifequal <- LP m [Tok] -> LP m [Tok]
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m a
withVerbatimMode LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
[Tok]
ifnotequal <- LP m [Tok] -> LP m [Tok]
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m a
withVerbatimMode LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
TokStream Bool
_ [Tok]
ts <- ParsecT TokStream LaTeXState m TokStream
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
if Inlines
str1 Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
str2
then TokStream -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput (TokStream -> ParsecT TokStream LaTeXState m ())
-> TokStream -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> [Tok] -> TokStream
TokStream Bool
False ([Tok]
ifequal [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++ [Tok]
ts)
else TokStream -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput (TokStream -> ParsecT TokStream LaTeXState m ())
-> TokStream -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> [Tok] -> TokStream
TokStream Bool
False ([Tok]
ifnotequal [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++ [Tok]
ts)
a -> LP m a
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty
coloredInline :: PandocMonad m => Text -> LP m Inlines
coloredInline :: forall (m :: * -> *). PandocMonad m => Text -> LP m Inlines
coloredInline Text
stylename = do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
[Tok]
color <- LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Attr -> Inlines -> Inlines
spanWith (Text
"",[],[(Text
"style",Text
stylename Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
": " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
color)]) (Inlines -> Inlines) -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
processHBox :: Inlines -> Inlines
processHBox :: Inlines -> Inlines
processHBox = (Inline -> Inline) -> Inlines -> Inlines
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
convert
where
convert :: Inline -> Inline
convert Inline
Space = Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton (Char -> Text) -> Char -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Char
chr Int
160
convert Inline
SoftBreak = Text -> Inline
Str (Text -> Inline) -> Text -> Inline
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton (Char -> Text) -> Char -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Char
chr Int
160
convert Inline
LineBreak = Text -> Inline
Str Text
""
convert Inline
x = Inline
x
isBlockCommand :: Text -> Bool
isBlockCommand :: Text -> Bool
isBlockCommand Text
s =
Text
s Text -> Map Text (LP PandocPure Blocks) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`M.member` (Map Text (LP PandocPure Blocks)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Blocks)
blockCommands :: M.Map Text (LP PandocPure Blocks))
Bool -> Bool -> Bool
|| Text
s Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
treatAsBlock
treatAsBlock :: Set.Set Text
treatAsBlock :: Set Text
treatAsBlock = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList
[ Text
"special", Text
"pdfannot", Text
"pdfstringdef"
, Text
"bibliographystyle"
, Text
"maketitle", Text
"makeindex", Text
"makeglossary"
, Text
"addcontentsline", Text
"addtocontents", Text
"addtocounter"
, Text
"ignore"
, Text
"hyperdef"
, Text
"markboth", Text
"markright", Text
"markleft"
, Text
"hspace", Text
"vspace"
, Text
"newpage"
, Text
"clearpage"
, Text
"pagebreak"
, Text
"titleformat"
, Text
"listoffigures"
, Text
"listoftables"
, Text
"write"
]
isInlineCommand :: Text -> Bool
isInlineCommand :: Text -> Bool
isInlineCommand Text
s =
Text
s Text -> Map Text (LP PandocPure Inlines) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`M.member` (Map Text (LP PandocPure Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
inlineCommands :: M.Map Text (LP PandocPure Inlines))
Bool -> Bool -> Bool
|| Text
s Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
treatAsInline
treatAsInline :: Set.Set Text
treatAsInline :: Set Text
treatAsInline = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList
[ Text
"index"
, Text
"hspace"
, Text
"vspace"
, Text
"noindent"
, Text
"newpage"
, Text
"clearpage"
, Text
"pagebreak"
]
lookupListDefault :: (Ord k) => v -> [k] -> M.Map k v -> v
lookupListDefault :: forall k v. Ord k => v -> [k] -> Map k v -> v
lookupListDefault v
d = (v -> Maybe v -> v
forall a. a -> Maybe a -> a
fromMaybe v
d (Maybe v -> v) -> (Map k v -> Maybe v) -> Map k v -> v
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Map k v -> Maybe v) -> Map k v -> v)
-> ([k] -> Map k v -> Maybe v) -> [k] -> Map k v -> v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [k] -> Map k v -> Maybe v
forall {a} {a}. Ord a => [a] -> Map a a -> Maybe a
lookupList
where lookupList :: [a] -> Map a a -> Maybe a
lookupList [a]
l Map a a
m = [Maybe a] -> Maybe a
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum ([Maybe a] -> Maybe a) -> [Maybe a] -> Maybe a
forall a b. (a -> b) -> a -> b
$ (a -> Maybe a) -> [a] -> [Maybe a]
forall a b. (a -> b) -> [a] -> [b]
map (a -> Map a a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
`M.lookup` Map a a
m) [a]
l
inline :: PandocMonad m => LP m Inlines
inline :: forall (m :: * -> *). PandocMonad m => LP m Inlines
inline = do
Tok SourcePos
pos TokType
toktype Text
t <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
peekTok
let eatOneToken :: LP m Tok
eatOneToken = (Tok -> Bool) -> LP m Tok
forall (m :: * -> *). PandocMonad m => (Tok -> Bool) -> LP m Tok
satisfyTok (Bool -> Tok -> Bool
forall a b. a -> b -> a
const Bool
True)
let symbolAsString :: LP m Inlines
symbolAsString = Text -> Inlines
str Text
t Inlines -> LP m Tok -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Tok
eatOneToken
let unescapedSymbolAsString :: LP m Inlines
unescapedSymbolAsString =
do LP m Tok
eatOneToken
LogMessage -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT TokStream LaTeXState m ())
-> LogMessage -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
ParsingUnescaped Text
t SourcePos
pos
Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> LP m Inlines) -> Inlines -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str Text
t
case TokType
toktype of
TokType
Comment -> Inlines
forall a. Monoid a => a
mempty Inlines -> LP m Tok -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Tok
eatOneToken
TokType
Spaces -> Inlines
space Inlines -> LP m Tok -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Tok
eatOneToken
TokType
Newline -> Inlines
softbreak Inlines -> ParsecT TokStream LaTeXState m () -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
endline
TokType
Word -> Text -> Inlines
str Text
t Inlines -> LP m Tok -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Tok
eatOneToken
TokType
Symbol ->
case Text
t of
Text
"-" -> LP m Tok
eatOneToken LP m Tok -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Text -> Inlines
str Text
"-") (Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'-' LP m Tok -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Text -> Inlines
str Text
"–") (Text -> Inlines
str Text
"—" Inlines -> LP m Tok -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'-'))
Text
"'" -> LP m Tok
eatOneToken LP m Tok -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Inlines -> LP m Inlines -> LP m Inlines
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Text -> Inlines
str Text
"’") (Text -> Inlines
str Text
"”" Inlines -> LP m Tok -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\'')
Text
"~" -> Text -> Inlines
str Text
"\160" Inlines -> LP m Tok -> LP m Inlines
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Tok
eatOneToken
Text
"`" -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doubleQuote LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
singleQuote LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
symbolAsString
Text
"\"" -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doubleQuote LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
singleQuote LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
symbolAsString
Text
"“" -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doubleQuote LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
symbolAsString
Text
"‘" -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
singleQuote LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
symbolAsString
Text
"$" -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
dollarsMath LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
unescapedSymbolAsString
Text
"|" -> (Extension -> ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_literate_haskell ParsecT TokStream LaTeXState m () -> LP m Tok -> LP m Tok
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
LP m Tok
eatOneToken LP m Tok -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doLHSverb) LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
symbolAsString
Text
"{" -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineGroup
Text
"#" -> LP m Inlines
unescapedSymbolAsString
Text
"&" -> LP m Inlines
unescapedSymbolAsString
Text
"_" -> LP m Inlines
unescapedSymbolAsString
Text
"^" -> LP m Inlines
unescapedSymbolAsString
Text
"\\" -> LP m Inlines
forall a. ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
Text
"}" -> LP m Inlines
forall a. ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
Text
_ -> LP m Inlines
symbolAsString
CtrlSeq Text
_ -> (Text -> Inlines) -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
(Text -> a) -> LP m a
macroDef (Text -> Text -> Inlines
rawInline Text
"latex")
LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineGroup
LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineCommand'
LP m Inlines -> LP m Inlines -> LP m Inlines
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineEnvironment
TokType
Esc1 -> Text -> Inlines
str (Text -> Inlines) -> (Char -> Text) -> Char -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton (Char -> Inlines)
-> ParsecT TokStream LaTeXState m Char -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Char
forall (m :: * -> *). PandocMonad m => LP m Char
primEscape
TokType
Esc2 -> Text -> Inlines
str (Text -> Inlines) -> (Char -> Text) -> Char -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton (Char -> Inlines)
-> ParsecT TokStream LaTeXState m Char -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Char
forall (m :: * -> *). PandocMonad m => LP m Char
primEscape
TokType
_ -> LP m Inlines
forall a. ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
inlines :: PandocMonad m => LP m Inlines
inlines :: forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT TokStream LaTeXState m [Inlines]
-> ParsecT TokStream LaTeXState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m [Inlines]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
opt :: PandocMonad m => LP m Inlines
opt :: forall (m :: * -> *). PandocMonad m => LP m Inlines
opt = do
[Tok]
toks <- ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp LP m ()
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracketedToks ParsecT TokStream LaTeXState m [Tok]
-> LP m () -> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp)
LaTeXState
st <- ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Either ParseError Inlines
parsed <- ParsecT
TokStream LaTeXState (ParsecT TokStream LaTeXState m) Inlines
-> LaTeXState
-> String
-> TokStream
-> ParsecT TokStream LaTeXState m (Either ParseError Inlines)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> String -> s -> m (Either ParseError a)
runParserT ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT
TokStream LaTeXState (ParsecT TokStream LaTeXState m) [Inlines]
-> ParsecT
TokStream LaTeXState (ParsecT TokStream LaTeXState m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT
TokStream LaTeXState (ParsecT TokStream LaTeXState m) Inlines
-> ParsecT
TokStream LaTeXState (ParsecT TokStream LaTeXState m) [Inlines]
forall a.
ParsecT TokStream LaTeXState (ParsecT TokStream LaTeXState m) a
-> ParsecT
TokStream LaTeXState (ParsecT TokStream LaTeXState m) [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT
TokStream LaTeXState (ParsecT TokStream LaTeXState m) Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline) LaTeXState
st String
"bracketed option"
(Bool -> [Tok] -> TokStream
TokStream Bool
False [Tok]
toks)
case Either ParseError Inlines
parsed of
Right Inlines
result -> Inlines -> LP m Inlines
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
result
Left ParseError
e -> PandocError -> LP m Inlines
forall a. PandocError -> ParsecT TokStream LaTeXState m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> LP m Inlines) -> PandocError -> LP m Inlines
forall a b. (a -> b) -> a -> b
$ Sources -> ParseError -> PandocError
fromParsecError ([Tok] -> Sources
forall a. ToSources a => a -> Sources
toSources [Tok]
toks) ParseError
e
preamble :: PandocMonad m => LP m Blocks
preamble :: forall (m :: * -> *). PandocMonad m => LP m Blocks
preamble = [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT TokStream LaTeXState m [Blocks]
-> ParsecT TokStream LaTeXState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m [Blocks]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT TokStream LaTeXState m Blocks
preambleBlock
where preambleBlock :: ParsecT TokStream LaTeXState m Blocks
preambleBlock = (Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1)
ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Text -> Blocks) -> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
(Text -> a) -> LP m a
macroDef (Text -> Text -> Blocks
rawBlock Text
"latex")
ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
filecontents
ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blockCommand)
ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced)
ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (Text -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => Text -> LP m ()
begin_ Text
"document")
LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok
Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty)
rule :: PandocMonad m => LP m Blocks
rule :: forall (m :: * -> *). PandocMonad m => LP m Blocks
rule = do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
Text
width <- (Char -> Bool) -> Text -> Text
T.takeWhile (\Char
c -> Char -> Bool
isDigit Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') (Text -> Text) -> (Inlines -> Text) -> Inlines -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify (Inlines -> Text)
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
Inlines
_thickness <- ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
case Text -> Maybe Double
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead Text
width of
Just (Double
0 :: Double) -> Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
Maybe Double
_ -> Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
horizontalRule
paragraph :: PandocMonad m => LP m Blocks
paragraph :: forall (m :: * -> *). PandocMonad m => LP m Blocks
paragraph = do
Inlines
x <- Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT TokStream LaTeXState m [Inlines]
-> ParsecT TokStream LaTeXState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m [Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
if Inlines
x Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
forall a. Monoid a => a
mempty
then Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
else Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
para Inlines
x
rawBlockOr :: PandocMonad m => Text -> LP m Blocks -> LP m Blocks
rawBlockOr :: forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Blocks -> LP m Blocks
rawBlockOr Text
name LP m Blocks
fallback = do
Bool
parseRaw <- Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_raw_tex (Extensions -> Bool)
-> ParsecT TokStream LaTeXState m Extensions
-> ParsecT TokStream LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ReaderOptions -> Extensions)
-> ParsecT TokStream LaTeXState 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 LaTeXState m b
getOption ReaderOptions -> Extensions
readerExtensions
if Bool
parseRaw
then Text -> Text -> Blocks
rawBlock Text
"latex" (Text -> Blocks)
-> ParsecT TokStream LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> Text -> LP m Text
getRawCommand Text
name (Text
"\\" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name)
else LP m Blocks
fallback
doSubfile :: PandocMonad m => LP m Blocks
doSubfile :: forall (m :: * -> *). PandocMonad m => LP m Blocks
doSubfile = do
ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt
String
f <- Text -> String
T.unpack (Text -> String) -> ([Tok] -> Text) -> [Tok] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
removeDoubleQuotes (Text -> Text) -> ([Tok] -> Text) -> [Tok] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip (Text -> Text) -> ([Tok] -> Text) -> [Tok] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> String)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
TokStream
oldToks <- ParsecT TokStream LaTeXState m TokStream
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
TokStream -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput (TokStream -> ParsecT TokStream LaTeXState m ())
-> TokStream -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> [Tok] -> TokStream
TokStream Bool
False []
String -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => String -> LP m ()
insertIncluded ((String -> Bool) -> String -> String -> String
ensureExtension (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"") String
".tex" String
f)
Blocks
bs <- LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
TokStream -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput TokStream
oldToks
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
bs
include :: (PandocMonad m, Monoid a) => Text -> LP m a
include :: forall (m :: * -> *) a. (PandocMonad m, Monoid a) => Text -> LP m a
include Text
name = do
let isAllowed :: String -> Bool
isAllowed =
case Text
name of
Text
"include" -> (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
".tex")
Text
"input" -> (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"")
Text
_ -> Bool -> String -> Bool
forall a b. a -> b -> a
const Bool
False
ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt
[String]
fs <- (Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> String
T.unpack (Text -> String) -> (Text -> Text) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
removeDoubleQuotes (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip) ([Text] -> [String]) -> ([Tok] -> [Text]) -> [Tok] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
"," (Text -> [Text]) -> ([Tok] -> Text) -> [Tok] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Tok] -> Text
untokenize ([Tok] -> [String])
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
(String -> ParsecT TokStream LaTeXState m ())
-> [String] -> ParsecT TokStream LaTeXState m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (String -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => String -> LP m ()
insertIncluded (String -> ParsecT TokStream LaTeXState m ())
-> (String -> String)
-> String
-> ParsecT TokStream LaTeXState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> String -> String -> String
ensureExtension String -> Bool
isAllowed String
".tex") [String]
fs
a -> LP m a
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty
usepackage :: (PandocMonad m, Monoid a) => LP m a
usepackage :: forall (m :: * -> *) a. (PandocMonad m, Monoid a) => LP m a
usepackage = do
ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt
[String]
fs <- (Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> String
T.unpack (Text -> String) -> (Text -> Text) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
removeDoubleQuotes (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip) ([Text] -> [String]) -> ([Tok] -> [Text]) -> [Tok] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
"," (Text -> [Text]) -> ([Tok] -> Text) -> [Tok] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Tok] -> Text
untokenize ([Tok] -> [String])
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
let parsePackage :: String -> ParsecT TokStream LaTeXState m ()
parsePackage String
f = do
TokStream Bool
_ [Tok]
ts <- String -> LP m TokStream
forall (m :: * -> *). PandocMonad m => String -> LP m TokStream
getIncludedToks ((String -> Bool) -> String -> String -> String
ensureExtension (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
".sty") String
".sty" String
f)
ParsecT TokStream LaTeXState m ()
-> [Tok] -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a. PandocMonad m => LP m a -> [Tok] -> LP m a
parseFromToks (do Blocks
_ <- LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
do SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
LogMessage -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT TokStream LaTeXState m ())
-> LogMessage -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
CouldNotParseIncludeFile (String -> Text
T.pack String
f) SourcePos
pos)
[Tok]
ts
(String -> ParsecT TokStream LaTeXState m ())
-> [String] -> ParsecT TokStream LaTeXState m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => String -> LP m ()
parsePackage [String]
fs
a -> LP m a
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty
readFileFromTexinputs :: PandocMonad m => FilePath -> LP m (Maybe Text)
readFileFromTexinputs :: forall (m :: * -> *). PandocMonad m => String -> LP m (Maybe Text)
readFileFromTexinputs String
fp = do
Map Text Text
fileContentsMap <- LaTeXState -> Map Text Text
sFileContents (LaTeXState -> Map Text Text)
-> ParsecT TokStream LaTeXState m LaTeXState
-> ParsecT TokStream LaTeXState m (Map Text Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
case Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (String -> Text
T.pack String
fp) Map Text Text
fileContentsMap of
Just Text
t -> Maybe Text -> LP m (Maybe Text)
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t)
Maybe Text
Nothing -> do
[String]
dirs <- (Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\Text
t -> if Text -> Bool
T.null Text
t
then String
"."
else Text -> String
T.unpack Text
t)
([Text] -> [String])
-> (Maybe Text -> [Text]) -> Maybe Text -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
':') (Text -> [Text]) -> (Maybe Text -> Text) -> Maybe Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
""
(Maybe Text -> [String])
-> LP m (Maybe Text) -> ParsecT TokStream LaTeXState m [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> LP m (Maybe Text)
forall (m :: * -> *). PandocMonad m => Text -> m (Maybe Text)
lookupEnv Text
"TEXINPUTS"
[String] -> String -> LP m (Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
[String] -> String -> m (Maybe Text)
readFileFromDirs [String]
dirs String
fp
ensureExtension :: (FilePath -> Bool) -> FilePath -> FilePath -> FilePath
ensureExtension :: (String -> Bool) -> String -> String -> String
ensureExtension String -> Bool
isAllowed String
defaultExt String
fp =
let ext :: String
ext = String -> String
takeExtension String
fp
in if String -> Bool
isAllowed String
ext
then String
fp
else String -> String -> String
addExtension String
fp String
defaultExt
getIncludedToks :: PandocMonad m
=> FilePath
-> LP m TokStream
getIncludedToks :: forall (m :: * -> *). PandocMonad m => String -> LP m TokStream
getIncludedToks String
f = do
SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
[Text]
containers <- LaTeXState -> [Text]
forall st. HasIncludeFiles st => st -> [Text]
getIncludeFiles (LaTeXState -> [Text])
-> ParsecT TokStream LaTeXState m LaTeXState
-> ParsecT TokStream LaTeXState m [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String -> Text
T.pack String
f Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
containers) (ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$
PandocError -> ParsecT TokStream LaTeXState m ()
forall a. PandocError -> ParsecT TokStream LaTeXState m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> ParsecT TokStream LaTeXState m ())
-> PandocError -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocParseError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Include file loop at " String -> String -> String
forall a. [a] -> [a] -> [a]
++ SourcePos -> String
forall a. Show a => a -> String
show SourcePos
pos
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> LaTeXState -> LaTeXState
forall st. HasIncludeFiles st => Text -> st -> st
addIncludeFile (Text -> LaTeXState -> LaTeXState)
-> Text -> LaTeXState -> LaTeXState
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
f
Maybe Text
mbcontents <- String -> LP m (Maybe Text)
forall (m :: * -> *). PandocMonad m => String -> LP m (Maybe Text)
readFileFromTexinputs String
f
Text
contents <- case Maybe Text
mbcontents of
Just Text
s -> Text -> ParsecT TokStream LaTeXState m Text
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
s
Maybe Text
Nothing -> do
LogMessage -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT TokStream LaTeXState m ())
-> LogMessage -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
CouldNotLoadIncludeFile (String -> Text
T.pack String
f) SourcePos
pos
Text -> ParsecT TokStream LaTeXState m Text
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState LaTeXState -> LaTeXState
forall st. HasIncludeFiles st => st -> st
dropLatestIncludeFile
TokStream -> LP m TokStream
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (TokStream -> LP m TokStream) -> TokStream -> LP m TokStream
forall a b. (a -> b) -> a -> b
$ Bool -> [Tok] -> TokStream
TokStream Bool
False ([Tok] -> TokStream) -> [Tok] -> TokStream
forall a b. (a -> b) -> a -> b
$ SourcePos -> Text -> [Tok]
tokenize (String -> SourcePos
initialPos String
f) Text
contents
insertIncluded :: PandocMonad m
=> FilePath
-> LP m ()
insertIncluded :: forall (m :: * -> *). PandocMonad m => String -> LP m ()
insertIncluded String
f = do
TokStream
contents <- String -> LP m TokStream
forall (m :: * -> *). PandocMonad m => String -> LP m TokStream
getIncludedToks String
f
TokStream
ts <- LP m TokStream
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
TokStream -> LP m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput (TokStream -> LP m ()) -> TokStream -> LP m ()
forall a b. (a -> b) -> a -> b
$ TokStream
contents TokStream -> TokStream -> TokStream
forall a. Semigroup a => a -> a -> a
<> TokStream
ts
authors :: PandocMonad m => LP m ()
authors :: forall (m :: * -> *). PandocMonad m => LP m ()
authors = ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ do
LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
bgroup
let oneAuthor :: ParsecT TokStream LaTeXState m Inlines
oneAuthor = [Block] -> Inlines
blocksToInlines' ([Block] -> Inlines)
-> ([Blocks] -> [Block]) -> [Blocks] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> [Block]
forall a. Many a -> [a]
B.toList (Blocks -> [Block]) -> ([Blocks] -> Blocks) -> [Blocks] -> [Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Inlines)
-> ParsecT TokStream LaTeXState m [Blocks]
-> ParsecT TokStream LaTeXState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m [Blocks]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
[Inlines]
auths <- ParsecT TokStream LaTeXState m Inlines
-> LP m Tok -> ParsecT TokStream LaTeXState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
sepBy ParsecT TokStream LaTeXState m Inlines
oneAuthor (Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"and")
LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
egroup
Text -> [Inlines] -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"author" ((Inlines -> Inlines) -> [Inlines] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map Inlines -> Inlines
trimInlines [Inlines]
auths)
looseItem :: PandocMonad m => LP m Blocks
looseItem :: forall (m :: * -> *). PandocMonad m => LP m Blocks
looseItem = do
Bool
inListItem <- LaTeXState -> Bool
sInListItem (LaTeXState -> Bool)
-> ParsecT TokStream LaTeXState m LaTeXState
-> ParsecT TokStream LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not Bool
inListItem
ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
epigraph :: PandocMonad m => LP m Blocks
epigraph :: forall (m :: * -> *). PandocMonad m => LP m Blocks
epigraph = do
Blocks
p1 <- LP m Blocks -> LP m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
Blocks
p2 <- LP m Blocks -> LP m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
divWith (Text
"", [Text
"epigraph"], []) (Blocks
p1 Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
p2)
section :: PandocMonad m => Attr -> Int -> LP m Blocks
section :: forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section (Text
ident, [Text]
classes, [(Text, Text)]
kvs) Int
lvl = do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
Inlines
contents <- LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline
Text
lab <- Text
-> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState 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
ident (ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m Text)
-> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m Text
forall a b. (a -> b) -> a -> b
$
ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces LP m ()
-> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m Tok
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"label"
ParsecT TokStream LaTeXState m Tok -> LP m () -> LP m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces LP m ()
-> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m Text
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced)
Bool -> LP m () -> LP m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
lvl Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (LP m () -> LP m ()) -> LP m () -> LP m ()
forall a b. (a -> b) -> a -> b
$
(LaTeXState -> LaTeXState) -> LP m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> LP m ())
-> (LaTeXState -> LaTeXState) -> LP m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sHasChapters = True }
Bool -> LP m () -> LP m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text
"unnumbered" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes) (LP m () -> LP m ()) -> LP m () -> LP m ()
forall a b. (a -> b) -> a -> b
$ do
DottedNum
hn <- LaTeXState -> DottedNum
sLastHeaderNum (LaTeXState -> DottedNum)
-> ParsecT TokStream LaTeXState m LaTeXState
-> ParsecT TokStream LaTeXState m DottedNum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
Bool
hasChapters <- LaTeXState -> Bool
sHasChapters (LaTeXState -> Bool)
-> ParsecT TokStream LaTeXState m LaTeXState
-> ParsecT TokStream LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let lvl' :: Int
lvl' = Int
lvl Int -> Int -> Int
forall a. Num a => a -> a -> a
+ if Bool
hasChapters then Int
1 else Int
0
let num :: DottedNum
num = Int -> DottedNum -> DottedNum
incrementDottedNum Int
lvl' DottedNum
hn
(LaTeXState -> LaTeXState) -> LP m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> LP m ())
-> (LaTeXState -> LaTeXState) -> LP m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sLastHeaderNum = num
, sLabels = M.insert lab
[Str (renderDottedNum num)]
(sLabels st) }
Attr
attr' <- Attr -> Inlines -> ParsecT TokStream LaTeXState m Attr
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
HasIdentifierList st) =>
Attr -> Inlines -> ParsecT s st m Attr
registerHeader (Text
lab, [Text]
classes, [(Text, Text)]
kvs) Inlines
contents
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Inlines -> Blocks
headerWith Attr
attr' Int
lvl Inlines
contents
blockCommand :: PandocMonad m => LP m Blocks
blockCommand :: forall (m :: * -> *). PandocMonad m => LP m Blocks
blockCommand = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
Tok SourcePos
_ (CtrlSeq Text
name) Text
txt <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyControlSeq
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"begin" Bool -> Bool -> Bool
&& Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"end" Bool -> Bool -> Bool
&& Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"and"
Text
star <- Text
-> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState 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
"" (Text
"*" Text -> LP m Tok -> ParsecT TokStream LaTeXState m Text
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'*' ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Text
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp)
let name' :: Text
name' = Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
star
let names :: [Text]
names = [Text] -> [Text]
forall a. Ord a => [a] -> [a]
nubOrd [Text
name', Text
name]
let rawDefiniteBlock :: ParsecT TokStream LaTeXState m Blocks
rawDefiniteBlock = do
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> Bool
isBlockCommand Text
name
Text
rawcontents <- Text -> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> Text -> LP m Text
getRawCommand Text
name (Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
star)
(Extension -> ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_tex ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Blocks
rawBlock Text
"latex" Text
rawcontents))
ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> ParsecT TokStream LaTeXState m Blocks
forall a (m :: * -> *) s u.
(Monoid a, PandocMonad m) =>
Text -> ParsecT s u m a
ignore Text
rawcontents
let startCommand :: ParsecT TokStream LaTeXState m ()
startCommand = ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ do
Tok SourcePos
_ (CtrlSeq Text
n) Text
_ <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyControlSeq
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text
"start" Text -> Text -> Bool
`T.isPrefixOf` Text
n
let rawMaybeBlock :: ParsecT TokStream LaTeXState m Blocks
rawMaybeBlock = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Bool
isInlineCommand Text
name
Text
rawcontents <- Text -> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> Text -> LP m Text
getRawCommand Text
name (Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
star)
Blocks
curr <- (Extension -> ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_raw_tex ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Blocks
rawBlock Text
"latex" Text
rawcontents))
ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> ParsecT TokStream LaTeXState m Blocks
forall a (m :: * -> *) s u.
(Monoid a, PandocMonad m) =>
Text -> ParsecT s u m a
ignore Text
rawcontents
[Blocks]
rest <- ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m [Blocks]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m [Blocks])
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m [Blocks]
forall a b. (a -> b) -> a -> b
$ ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT TokStream LaTeXState m ()
startCommand ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blockCommand
ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
blankline ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT TokStream LaTeXState m ()
startCommand
Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT TokStream LaTeXState m Blocks)
-> Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks
curr Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
rest
let raw :: ParsecT TokStream LaTeXState m Blocks
raw = ParsecT TokStream LaTeXState m Blocks
rawDefiniteBlock ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT TokStream LaTeXState m Blocks
rawMaybeBlock
ParsecT TokStream LaTeXState m Blocks
-> [Text]
-> Map Text (ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
forall k v. Ord k => v -> [k] -> Map k v -> v
lookupListDefault ParsecT TokStream LaTeXState m Blocks
raw [Text]
names Map Text (ParsecT TokStream LaTeXState m Blocks)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Blocks)
blockCommands
closing :: PandocMonad m => LP m Blocks
closing :: forall (m :: * -> *). PandocMonad m => LP m Blocks
closing = do
Inlines
contents <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
LaTeXState
st <- ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let extractInlines :: MetaValue -> [Inline]
extractInlines (MetaBlocks [Plain [Inline]
ys]) = [Inline]
ys
extractInlines (MetaBlocks [Para [Inline]
ys ]) = [Inline]
ys
extractInlines MetaValue
_ = []
let sigs :: Blocks
sigs = case Text -> Meta -> Maybe MetaValue
lookupMeta Text
"author" (LaTeXState -> Meta
sMeta LaTeXState
st) of
Just (MetaList [MetaValue]
xs) ->
Inlines -> Blocks
para (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
trimInlines (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ [Inline] -> Inlines
forall a. [a] -> Many a
fromList ([Inline] -> Inlines) -> [Inline] -> Inlines
forall a b. (a -> b) -> a -> b
$
[Inline] -> [[Inline]] -> [Inline]
forall a. [a] -> [[a]] -> [a]
intercalate [Inline
LineBreak] ([[Inline]] -> [Inline]) -> [[Inline]] -> [Inline]
forall a b. (a -> b) -> a -> b
$ (MetaValue -> [Inline]) -> [MetaValue] -> [[Inline]]
forall a b. (a -> b) -> [a] -> [b]
map MetaValue -> [Inline]
extractInlines [MetaValue]
xs
Maybe MetaValue
_ -> Blocks
forall a. Monoid a => a
mempty
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
para (Inlines -> Inlines
trimInlines Inlines
contents) Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
sigs
parbox :: PandocMonad m => LP m Blocks
parbox :: forall (m :: * -> *). PandocMonad m => LP m Blocks
parbox = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Bool
oldInTableCell <- LaTeXState -> Bool
sInTableCell (LaTeXState -> Bool)
-> ParsecT TokStream LaTeXState m LaTeXState
-> ParsecT TokStream LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(LaTeXState -> LaTeXState) -> LP m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> LP m ())
-> (LaTeXState -> LaTeXState) -> LP m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sInTableCell = False }
Blocks
res <- ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
(LaTeXState -> LaTeXState) -> LP m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> LP m ())
-> (LaTeXState -> LaTeXState) -> LP m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sInTableCell = oldInTableCell }
Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res
blockCommands :: PandocMonad m => M.Map Text (LP m Blocks)
blockCommands :: forall (m :: * -> *). PandocMonad m => Map Text (LP m Blocks)
blockCommands = [(Text, LP m Blocks)] -> Map Text (LP m Blocks)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"par", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts)
, (Text
"parbox", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
parbox)
, (Text
"title", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
(LP m Inlines -> LP m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"title")
ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (LP m Blocks -> LP m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block LP m Blocks
-> (Blocks -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Blocks -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"title")))
, (Text
"subtitle", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"subtitle"))
, (Text
"author", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
authors))
, (Text
"address", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"address"))
, (Text
"signature", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
authors))
, (Text
"date", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"date"))
, (Text
"newtheorem", LP m Inlines -> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m Blocks
newtheorem LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline)
, (Text
"theoremstyle", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
theoremstyle)
, (Text
"extratitle", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"extratitle"))
, (Text
"frontispiece", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"frontispiece"))
, (Text
"titlehead", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"titlehead"))
, (Text
"subject", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"subject"))
, (Text
"publishers", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"publishers"))
, (Text
"uppertitleback", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"uppertitleback"))
, (Text
"lowertitleback", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"lowertitleback"))
, (Text
"dedication", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines
-> (Inlines -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"dedication"))
, (Text
"part", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr (-Int
1))
, (Text
"part*", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section (Text
"",[Text
"unnumbered"],[]) (-Int
1))
, (Text
"chapter", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr Int
0)
, (Text
"chapter*", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section (Text
"",[Text
"unnumbered"],[]) Int
0)
, (Text
"section", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr Int
1)
, (Text
"section*", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section (Text
"",[Text
"unnumbered"],[]) Int
1)
, (Text
"subsection", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr Int
2)
, (Text
"subsection*", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section (Text
"",[Text
"unnumbered"],[]) Int
2)
, (Text
"subsubsection", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr Int
3)
, (Text
"subsubsection*", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section (Text
"",[Text
"unnumbered"],[]) Int
3)
, (Text
"paragraph", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr Int
4)
, (Text
"paragraph*", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section (Text
"",[Text
"unnumbered"],[]) Int
4)
, (Text
"subparagraph", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr Int
5)
, (Text
"subparagraph*", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section (Text
"",[Text
"unnumbered"],[]) Int
5)
, (Text
"frametitle", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr Int
3)
, (Text
"framesubtitle", Attr -> Int -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Attr -> Int -> LP m Blocks
section Attr
nullAttr Int
4)
, (Text
"opening", Inlines -> Blocks
para (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
trimInlines (Inlines -> Blocks) -> LP m Inlines -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok))
, (Text
"closing", ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
closing)
, (Text
"plainbreak", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"plainbreak*", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"fancybreak", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"fancybreak*", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"plainfancybreak", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"plainfancybreak*", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"pfbreak", Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"pfbreak*", Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"hrule", Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
, (Text
"strut", Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
forall a. Monoid a => a
mempty)
, (Text
"rule", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
rule)
, (Text
"item", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
looseItem)
, (Text
"documentclass", ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
preamble)
, (Text
"centerline", Inlines -> Blocks
para (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
trimInlines (Inlines -> Blocks) -> LP m Inlines -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok))
, (Text
"caption", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Inlines -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m Inlines -> LP m ()
setCaption LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline)
, (Text
"bibliography", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok]
-> ([Tok] -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
Text -> [Inlines] -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"bibliography" ([Inlines] -> ParsecT TokStream LaTeXState m ())
-> ([Tok] -> [Inlines])
-> [Tok]
-> ParsecT TokStream LaTeXState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Inlines]
splitBibs (Text -> [Inlines]) -> ([Tok] -> Text) -> [Tok] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize))
, (Text
"addbibresource", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok]
-> ([Tok] -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
Text -> [Inlines] -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"bibliography" ([Inlines] -> ParsecT TokStream LaTeXState m ())
-> ([Tok] -> [Inlines])
-> [Tok]
-> ParsecT TokStream LaTeXState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Inlines]
splitBibs (Text -> [Inlines]) -> ([Tok] -> Text) -> [Tok] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize))
, (Text
"endinput", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipSameFileToks)
, (Text
"lstinputlisting", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
inputListing)
, (Text
"inputminted", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
inputMinted)
, (Text
"graphicspath", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
graphicsPath)
, (Text
"setdefaultlanguage", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
setDefaultLanguage)
, (Text
"setmainlanguage", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
setDefaultLanguage)
, (Text
"hypertarget", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
hypertargetBlock)
, (Text
"textcolor", Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
coloredBlock Text
"color")
, (Text
"colorbox", Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
coloredBlock Text
"background-color")
, (Text
"blockquote", Bool -> Maybe Text -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Bool -> Maybe Text -> LP m Blocks
blockquote Bool
False Maybe Text
forall a. Maybe a
Nothing)
, (Text
"blockcquote", Bool -> Maybe Text -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Bool -> Maybe Text -> LP m Blocks
blockquote Bool
True Maybe Text
forall a. Maybe a
Nothing)
, (Text
"foreignblockquote", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> ([Tok] -> LP m Blocks) -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Maybe Text -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Bool -> Maybe Text -> LP m Blocks
blockquote Bool
False (Maybe Text -> LP m Blocks)
-> ([Tok] -> Maybe Text) -> [Tok] -> LP m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> ([Tok] -> Text) -> [Tok] -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize)
, (Text
"foreignblockcquote", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> ([Tok] -> LP m Blocks) -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Maybe Text -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Bool -> Maybe Text -> LP m Blocks
blockquote Bool
True (Maybe Text -> LP m Blocks)
-> ([Tok] -> Maybe Text) -> [Tok] -> LP m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> ([Tok] -> Text) -> [Tok] -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize)
, (Text
"hyphenblockquote", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> ([Tok] -> LP m Blocks) -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Maybe Text -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Bool -> Maybe Text -> LP m Blocks
blockquote Bool
False (Maybe Text -> LP m Blocks)
-> ([Tok] -> Maybe Text) -> [Tok] -> LP m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> ([Tok] -> Text) -> [Tok] -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize)
, (Text
"hyphenblockcquote", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> ([Tok] -> LP m Blocks) -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Maybe Text -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Bool -> Maybe Text -> LP m Blocks
blockquote Bool
True (Maybe Text -> LP m Blocks)
-> ([Tok] -> Maybe Text) -> [Tok] -> LP m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> ([Tok] -> Text) -> [Tok] -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize)
, (Text
"include", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Blocks -> LP m Blocks
rawBlockOr Text
"include" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> LP m Blocks
forall (m :: * -> *) a. (PandocMonad m, Monoid a) => Text -> LP m a
include Text
"include")
, (Text
"input", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Blocks -> LP m Blocks
rawBlockOr Text
"input" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> LP m Blocks
forall (m :: * -> *) a. (PandocMonad m, Monoid a) => Text -> LP m a
include Text
"input")
, (Text
"subfile", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Blocks -> LP m Blocks
rawBlockOr Text
"subfile" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
doSubfile)
, (Text
"usepackage", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
Text -> LP m Blocks -> LP m Blocks
rawBlockOr Text
"usepackage" LP m Blocks
forall (m :: * -> *) a. (PandocMonad m, Monoid a) => LP m a
usepackage)
, (Text
"PackageError", Blocks
forall a. Monoid a => a
mempty Blocks -> LP m [Tok] -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m [Tok] -> LP m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced))
, (Text
"epigraph", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
epigraph)
, (Text
"raggedright", Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
forall a. Monoid a => a
mempty)
]
skipSameFileToks :: PandocMonad m => LP m ()
skipSameFileToks :: forall (m :: * -> *). PandocMonad m => LP m ()
skipSameFileToks = do
SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
ParsecT TokStream LaTeXState m Tok -> LP m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT TokStream LaTeXState m Tok -> LP m ())
-> ParsecT TokStream LaTeXState m Tok -> LP m ()
forall a b. (a -> b) -> a -> b
$ String -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => String -> LP m Tok
infile (SourcePos -> String
sourceName SourcePos
pos)
environments :: PandocMonad m => M.Map Text (LP m Blocks)
environments :: forall (m :: * -> *). PandocMonad m => Map Text (LP m Blocks)
environments = Map Text (LP m Blocks)
-> Map Text (LP m Blocks) -> Map Text (LP m Blocks)
forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union (LP m Blocks -> LP m Inlines -> Map Text (LP m Blocks)
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Map Text (LP m Blocks)
tableEnvironments LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline) (Map Text (LP m Blocks) -> Map Text (LP m Blocks))
-> Map Text (LP m Blocks) -> Map Text (LP m Blocks)
forall a b. (a -> b) -> a -> b
$
[(Text, LP m Blocks)] -> Map Text (LP m Blocks)
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
[ (Text
"document", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"document" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks LP m Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok)
, (Text
"abstract", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"abstract" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks LP m Blocks
-> (Blocks -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Blocks -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"abstract"))
, (Text
"sloppypar", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"sloppypar" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
, (Text
"letter", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"letter" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
letterContents)
, (Text
"minipage", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"minipage" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$
ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m (Maybe [Tok])
-> ParsecT TokStream LaTeXState m (Maybe [Tok])
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m (Maybe [Tok])
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m (Maybe [Tok])
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces ParsecT TokStream LaTeXState m () -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
, (Text
"figure", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"figure" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
figure')
, (Text
"subfigure", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"subfigure" (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m () -> LP m Inlines -> LP m Inlines
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok LP m Inlines -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
figure')
, (Text
"center", Attr -> Blocks -> Blocks
divWith (Text
"", [Text
"center"], []) (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"center" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
, (Text
"quote", Blocks -> Blocks
blockQuote (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"quote" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
, (Text
"quotation", Blocks -> Blocks
blockQuote (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"quotation" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
, (Text
"verse", Blocks -> Blocks
blockQuote (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"verse" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
, (Text
"itemize", [Blocks] -> Blocks
bulletList ([Blocks] -> Blocks)
-> ParsecT TokStream LaTeXState m [Blocks] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT TokStream LaTeXState m [Blocks]
-> ParsecT TokStream LaTeXState m [Blocks]
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
listenv Text
"itemize" (LP m Blocks -> ParsecT TokStream LaTeXState m [Blocks]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
item))
, (Text
"description", [(Inlines, [Blocks])] -> Blocks
definitionList ([(Inlines, [Blocks])] -> Blocks)
-> ParsecT TokStream LaTeXState m [(Inlines, [Blocks])]
-> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT TokStream LaTeXState m [(Inlines, [Blocks])]
-> ParsecT TokStream LaTeXState m [(Inlines, [Blocks])]
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
listenv Text
"description" (ParsecT TokStream LaTeXState m (Inlines, [Blocks])
-> ParsecT TokStream LaTeXState m [(Inlines, [Blocks])]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT TokStream LaTeXState m (Inlines, [Blocks])
forall (m :: * -> *). PandocMonad m => LP m (Inlines, [Blocks])
descItem))
, (Text
"enumerate", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
orderedList')
, (Text
"alltt", Blocks -> Blocks
alltt (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"alltt" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
, (Text
"code", Extension -> ParsecT TokStream LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParsecT s st m ()
guardEnabled Extension
Ext_literate_haskell ParsecT TokStream LaTeXState m () -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
(Attr -> Text -> Blocks
codeBlockWith (Text
"",[Text
"haskell",Text
"literate"],[]) (Text -> Blocks)
-> ParsecT TokStream LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
"code"))
, (Text
"comment", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m Text -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
"comment")
, (Text
"verbatim", Text -> Blocks
codeBlock (Text -> Blocks)
-> ParsecT TokStream LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
"verbatim")
, (Text
"Verbatim", Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
fancyverbEnv Text
"Verbatim")
, (Text
"BVerbatim", Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
fancyverbEnv Text
"BVerbatim")
, (Text
"lstlisting", do Attr
attr <- [(Text, Text)] -> Attr
parseListingsOptions ([(Text, Text)] -> Attr)
-> ParsecT TokStream LaTeXState m [(Text, Text)]
-> ParsecT TokStream LaTeXState m Attr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Text)]
-> ParsecT TokStream LaTeXState m [(Text, Text)]
-> ParsecT TokStream LaTeXState 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 TokStream LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
Attr -> Text -> Blocks
codeBlockWith Attr
attr (Text -> Blocks)
-> ParsecT TokStream LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
"lstlisting")
, (Text
"minted", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
minted)
, (Text
"obeylines", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
obeylines)
, (Text
"tikzpicture", Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawVerbEnv Text
"tikzpicture")
, (Text
"tikzcd", Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawVerbEnv Text
"tikzcd")
, (Text
"lilypond", Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawVerbEnv Text
"lilypond")
, (Text
"ly", Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawVerbEnv Text
"ly")
, (Text
"proof", LP m Blocks -> LP m Inlines -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> LP m Blocks
proof LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt)
, (Text
"ifstrequal", LP m Blocks
forall (m :: * -> *) a. (PandocMonad m, Monoid a) => LP m a
ifstrequal)
, (Text
"newtoggle", ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok]
-> ([Tok] -> LP m Blocks) -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Tok] -> LP m Blocks
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
[Tok] -> LP m a
newToggle)
, (Text
"toggletrue", ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok]
-> ([Tok] -> LP m Blocks) -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> [Tok] -> LP m Blocks
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Bool -> [Tok] -> LP m a
setToggle Bool
True)
, (Text
"togglefalse", ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok]
-> ([Tok] -> LP m Blocks) -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> [Tok] -> LP m Blocks
forall a (m :: * -> *).
(Monoid a, PandocMonad m) =>
Bool -> [Tok] -> LP m a
setToggle Bool
False)
, (Text
"iftoggle", LP m Blocks -> LP m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m Blocks -> LP m Blocks) -> LP m Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
ifToggle ParsecT TokStream LaTeXState m () -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block)
, (Text
"CSLReferences", ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok] -> LP m Blocks -> LP m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"CSLReferences" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
, (Text
"otherlanguage", Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"otherlanguage" LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
otherlanguageEnv)
]
otherlanguageEnv :: PandocMonad m => LP m Blocks
otherlanguageEnv :: forall (m :: * -> *). PandocMonad m => LP m Blocks
otherlanguageEnv = do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
Text
babelLang <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
case Text -> Maybe Lang
babelLangToBCP47 Text
babelLang of
Just Lang
lang -> Attr -> Blocks -> Blocks
divWith (Text
"", [], [(Text
"lang", Lang -> Text
renderLang Lang
lang)]) (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
Maybe Lang
Nothing -> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
langEnvironment :: PandocMonad m => Text -> LP m Blocks
langEnvironment :: forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
langEnvironment Text
name =
case Text -> Maybe Lang
babelLangToBCP47 Text
name of
Just Lang
lang ->
Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
name (Attr -> Blocks -> Blocks
divWith (Text
"", [], [(Text
"lang", Lang -> Text
renderLang Lang
lang)]) (Blocks -> Blocks) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks)
Maybe Lang
Nothing -> LP m Blocks
forall a. ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
filecontents :: PandocMonad m => LP m Blocks
filecontents :: forall (m :: * -> *). PandocMonad m => LP m Blocks
filecontents = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"begin"
Text
name <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Bool -> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT TokStream LaTeXState m ())
-> Bool -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"filecontents" Bool -> Bool -> Bool
|| Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"filecontents*"
ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
Text
fp <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Text
txt <- Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
name
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st ->
LaTeXState
st{ sFileContents = M.insert fp txt (sFileContents st) }
Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
environment :: PandocMonad m => LP m Blocks
environment :: forall (m :: * -> *). PandocMonad m => LP m Blocks
environment = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"begin"
Text
name <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
ParsecT TokStream LaTeXState m Blocks
-> Text
-> Map Text (ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault ParsecT TokStream LaTeXState m Blocks
forall a. ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero Text
name Map Text (ParsecT TokStream LaTeXState m Blocks)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Blocks)
environments ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Text -> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
langEnvironment Text
name ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ParsecT TokStream LaTeXState m Blocks
-> LP m Inlines -> Text -> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Text -> LP m Blocks
theoremEnvironment ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt Text
name ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
if Text -> Map Text (LP PandocPure Inlines) -> Bool
forall k a. Ord k => k -> Map k a -> Bool
M.member Text
name (Map Text (LP PandocPure Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
inlineEnvironments
:: M.Map Text (LP PandocPure Inlines))
then ParsecT TokStream LaTeXState m Blocks
forall a. ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
else ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text -> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawEnv Text
name) ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawVerbEnv Text
name
rawEnv :: PandocMonad m => Text -> LP m Blocks
rawEnv :: forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawEnv Text
name = do
Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT TokStream LaTeXState 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 LaTeXState m b
getOption ReaderOptions -> Extensions
readerExtensions
let parseRaw :: Bool
parseRaw = Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_raw_tex Extensions
exts
Text
rawOptions <- [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text)
-> ParsecT TokStream LaTeXState m [Text]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Text
-> ParsecT TokStream LaTeXState m [Text]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => LP m Text
rawopt
let beginCommand :: Text
beginCommand = Text
"\\begin{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rawOptions
SourcePos
pos1 <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
if Bool
parseRaw
then do
(Blocks
_, [Tok]
raw) <- LP m Blocks -> LP m (Blocks, [Tok])
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m (a, [Tok])
withRaw (LP m Blocks -> LP m (Blocks, [Tok]))
-> LP m Blocks -> LP m (Blocks, [Tok])
forall a b. (a -> b) -> a -> b
$ Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
name LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Blocks
rawBlock Text
"latex"
(Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$ Text
beginCommand Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
raw
else do
Blocks
bs <- Text -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
name LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
LogMessage -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT TokStream LaTeXState m ())
-> LogMessage -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent Text
beginCommand SourcePos
pos1
SourcePos
pos2 <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
LogMessage -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT TokStream LaTeXState m ())
-> LogMessage -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent (Text
"\\end{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}") SourcePos
pos2
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
divWith (Text
"",[Text
name],[]) Blocks
bs
rawVerbEnv :: PandocMonad m => Text -> LP m Blocks
rawVerbEnv :: forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawVerbEnv Text
name = do
SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
(Text
_, [Tok]
raw) <- LP m Text -> LP m (Text, [Tok])
forall (m :: * -> *) a. PandocMonad m => LP m a -> LP m (a, [Tok])
withRaw (LP m Text -> LP m (Text, [Tok]))
-> LP m Text -> LP m (Text, [Tok])
forall a b. (a -> b) -> a -> b
$ Text -> LP m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
name
let raw' :: Text
raw' = Text
"\\begin{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
raw
Extensions
exts <- (ReaderOptions -> Extensions)
-> ParsecT TokStream LaTeXState 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 LaTeXState m b
getOption ReaderOptions -> Extensions
readerExtensions
let parseRaw :: Bool
parseRaw = Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_raw_tex Extensions
exts
if Bool
parseRaw
then Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Blocks
rawBlock Text
"latex" Text
raw'
else do
LogMessage -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT TokStream LaTeXState m ())
-> LogMessage -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent Text
raw' SourcePos
pos
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
fancyverbEnv :: PandocMonad m => Text -> LP m Blocks
fancyverbEnv :: forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
fancyverbEnv Text
name = do
[(Text, Text)]
options <- [(Text, Text)]
-> ParsecT TokStream LaTeXState m [(Text, Text)]
-> ParsecT TokStream LaTeXState 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 TokStream LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
let kvs :: [(Text, Text)]
kvs = [ (if Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"firstnumber"
then Text
"startFrom"
else Text
k, Text
v) | (Text
k,Text
v) <- [(Text, Text)]
options ]
let classes :: [Text]
classes = [ Text
"numberLines" |
Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"numbers" [(Text, Text)]
options Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"left" ]
let attr :: Attr
attr = (Text
"",[Text]
classes,[(Text, Text)]
kvs)
Attr -> Text -> Blocks
codeBlockWith Attr
attr (Text -> Blocks)
-> ParsecT TokStream LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
name
obeylines :: PandocMonad m => LP m Blocks
obeylines :: forall (m :: * -> *). PandocMonad m => LP m Blocks
obeylines =
Inlines -> Blocks
para (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Inlines
forall a. [a] -> Many a
fromList ([Inline] -> Inlines)
-> (Inlines -> [Inline]) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> [Inline]
removeLeadingTrailingBreaks ([Inline] -> [Inline])
-> (Inlines -> [Inline]) -> Inlines -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Inline -> Inline) -> [Inline] -> [Inline]
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
softBreakToHard ([Inline] -> [Inline])
-> (Inlines -> [Inline]) -> Inlines -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList (Inlines -> Blocks)
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"obeylines" ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines
where softBreakToHard :: Inline -> Inline
softBreakToHard Inline
SoftBreak = Inline
LineBreak
softBreakToHard Inline
x = Inline
x
removeLeadingTrailingBreaks :: [Inline] -> [Inline]
removeLeadingTrailingBreaks = [Inline] -> [Inline]
forall a. [a] -> [a]
reverse ([Inline] -> [Inline])
-> ([Inline] -> [Inline]) -> [Inline] -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Bool) -> [Inline] -> [Inline]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Inline -> Bool
isLineBreak ([Inline] -> [Inline])
-> ([Inline] -> [Inline]) -> [Inline] -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Inline] -> [Inline]
forall a. [a] -> [a]
reverse ([Inline] -> [Inline])
-> ([Inline] -> [Inline]) -> [Inline] -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Bool) -> [Inline] -> [Inline]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Inline -> Bool
isLineBreak
isLineBreak :: Inline -> Bool
isLineBreak Inline
LineBreak = Bool
True
isLineBreak Inline
_ = Bool
False
minted :: PandocMonad m => LP m Blocks
minted :: forall (m :: * -> *). PandocMonad m => LP m Blocks
minted = do
Attr
attr <- LP m Attr
forall (m :: * -> *). PandocMonad m => LP m Attr
mintedAttr
Attr -> Text -> Blocks
codeBlockWith Attr
attr (Text -> Blocks)
-> ParsecT TokStream LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT TokStream LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
"minted"
mintedAttr :: PandocMonad m => LP m Attr
mintedAttr :: forall (m :: * -> *). PandocMonad m => LP m Attr
mintedAttr = do
[(Text, Text)]
options <- [(Text, Text)]
-> ParsecT TokStream LaTeXState m [(Text, Text)]
-> ParsecT TokStream LaTeXState 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 TokStream LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
Text
lang <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
let kvs :: [(Text, Text)]
kvs = [ (if Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"firstnumber"
then Text
"startFrom"
else Text
k, Text
v) | (Text
k,Text
v) <- [(Text, Text)]
options ]
let classes :: [Text]
classes = [ Text
lang | Bool -> Bool
not (Text -> Bool
T.null Text
lang) ] [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++
[ Text
"numberLines" |
Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"linenos" [(Text, Text)]
options Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"true" ]
Attr -> LP m Attr
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
"",[Text]
classes,[(Text, Text)]
kvs)
inputMinted :: PandocMonad m => LP m Blocks
inputMinted :: forall (m :: * -> *). PandocMonad m => LP m Blocks
inputMinted = do
SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
Attr
attr <- LP m Attr
forall (m :: * -> *). PandocMonad m => LP m Attr
mintedAttr
Text
f <- (Char -> Bool) -> Text -> Text
T.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'"') (Text -> Text) -> ([Tok] -> Text) -> [Tok] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Maybe Text
mbCode <- String -> LP m (Maybe Text)
forall (m :: * -> *). PandocMonad m => String -> LP m (Maybe Text)
readFileFromTexinputs (Text -> String
T.unpack Text
f)
Text
rawcode <- case Maybe Text
mbCode of
Just Text
s -> Text -> ParsecT TokStream LaTeXState m Text
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
s
Maybe Text
Nothing -> do
LogMessage -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT TokStream LaTeXState m ())
-> LogMessage -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
CouldNotLoadIncludeFile Text
f SourcePos
pos
Text -> ParsecT TokStream LaTeXState m Text
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Blocks
B.codeBlockWith Attr
attr Text
rawcode
letterContents :: PandocMonad m => LP m Blocks
letterContents :: forall (m :: * -> *). PandocMonad m => LP m Blocks
letterContents = do
Blocks
bs <- LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
LaTeXState
st <- ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let addr :: Blocks
addr = case Text -> Meta -> Maybe MetaValue
lookupMeta Text
"address" (LaTeXState -> Meta
sMeta LaTeXState
st) of
Just (MetaBlocks [Plain [Inline]
xs]) ->
Inlines -> Blocks
para (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
trimInlines (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ [Inline] -> Inlines
forall a. [a] -> Many a
fromList [Inline]
xs
Maybe MetaValue
_ -> Blocks
forall a. Monoid a => a
mempty
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks
addr Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
bs
figure' :: PandocMonad m => LP m Blocks
figure' :: forall (m :: * -> *). PandocMonad m => LP m Blocks
figure' = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
resetCaption
[Either () Blocks]
innerContent <- ParsecT TokStream LaTeXState m (Either () Blocks)
-> ParsecT TokStream LaTeXState m [Either () Blocks]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT TokStream LaTeXState m (Either () Blocks)
-> ParsecT TokStream LaTeXState m [Either () Blocks])
-> ParsecT TokStream LaTeXState m (Either () Blocks)
-> ParsecT TokStream LaTeXState m [Either () Blocks]
forall a b. (a -> b) -> a -> b
$ ParsecT TokStream LaTeXState m (Either () Blocks)
-> ParsecT TokStream LaTeXState m (Either () Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (() -> Either () Blocks
forall a b. a -> Either a b
Left (() -> Either () Blocks)
-> LP m () -> ParsecT TokStream LaTeXState m (Either () Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
label) ParsecT TokStream LaTeXState m (Either () Blocks)
-> ParsecT TokStream LaTeXState m (Either () Blocks)
-> ParsecT TokStream LaTeXState m (Either () Blocks)
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Blocks -> Either () Blocks
forall a b. b -> Either a b
Right (Blocks -> Either () Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m (Either () Blocks)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block)
let content :: Blocks
content = (Block -> Block) -> Blocks -> Blocks
forall a b. Walkable a b => (a -> a) -> b -> b
walk Block -> Block
go (Blocks -> Blocks) -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall a b. (a -> b) -> a -> b
$ ([()], [Blocks]) -> [Blocks]
forall a b. (a, b) -> b
snd (([()], [Blocks]) -> [Blocks]) -> ([()], [Blocks]) -> [Blocks]
forall a b. (a -> b) -> a -> b
$ [Either () Blocks] -> ([()], [Blocks])
forall a b. [Either a b] -> ([a], [b])
partitionEithers [Either () Blocks]
innerContent
LaTeXState
st <- ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
let caption' :: Caption
caption' = Caption -> Maybe Caption -> Caption
forall a. a -> Maybe a -> a
fromMaybe Caption
B.emptyCaption (Maybe Caption -> Caption) -> Maybe Caption -> Caption
forall a b. (a -> b) -> a -> b
$ LaTeXState -> Maybe Caption
sCaption LaTeXState
st
let mblabel :: Maybe Text
mblabel = LaTeXState -> Maybe Text
sLastLabel LaTeXState
st
let attr :: Attr
attr = case Maybe Text
mblabel of
Just Text
lab -> (Text
lab, [], [])
Maybe Text
Nothing -> Attr
nullAttr
case Maybe Text
mblabel of
Maybe Text
Nothing -> () -> LP m ()
forall a. a -> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just Text
lab -> do
DottedNum
num <- (LaTeXState -> DottedNum) -> LP m DottedNum
forall (m :: * -> *).
Monad m =>
(LaTeXState -> DottedNum) -> LP m DottedNum
getNextNumber LaTeXState -> DottedNum
sLastFigureNum
LaTeXState -> LP m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState
LaTeXState
st { sLastFigureNum = num
, sLabels = M.insert lab [Str (renderDottedNum num)] (sLabels st)
}
Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT TokStream LaTeXState m Blocks)
-> Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Caption -> Blocks -> Blocks
B.figureWith Attr
attr Caption
caption' Blocks
content
where
go :: Block -> Block
go (Para [Image Attr
attr [Str Text
"image"] (Text, Text)
target]) = [Inline] -> Block
Plain [Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
attr [] (Text, Text)
target]
go Block
x = Block
x
coloredBlock :: PandocMonad m => Text -> LP m Blocks
coloredBlock :: forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
coloredBlock Text
stylename = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
[Tok]
color <- LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
ParsecT TokStream LaTeXState m Inlines -> LP m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (ParsecT TokStream LaTeXState m Inlines
-> ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT TokStream LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline)
let constructor :: Blocks -> Blocks
constructor = Attr -> Blocks -> Blocks
divWith (Text
"",[],[(Text
"style",Text
stylename Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
": " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
color)])
Blocks -> Blocks
constructor (Blocks -> Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
graphicsPath :: PandocMonad m => LP m Blocks
graphicsPath :: forall (m :: * -> *). PandocMonad m => LP m Blocks
graphicsPath = do
[String]
ps <- ([Tok] -> String) -> [[Tok]] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> String
T.unpack (Text -> String) -> ([Tok] -> Text) -> [Tok] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize) ([[Tok]] -> [String])
-> ParsecT TokStream LaTeXState m [[Tok]]
-> ParsecT TokStream LaTeXState m [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
bgroup LP m Tok
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m [[Tok]]
-> ParsecT TokStream LaTeXState m [[Tok]]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m [Tok]
-> LP m Tok -> ParsecT TokStream LaTeXState m [[Tok]]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill (ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces) LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
egroup)
ParsecT TokStream LaTeXState m [String]
forall (m :: * -> *). PandocMonad m => m [String]
getResourcePath ParsecT TokStream LaTeXState m [String]
-> ([String] -> ParsecT TokStream LaTeXState m ())
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> (a -> ParsecT TokStream LaTeXState m b)
-> ParsecT TokStream LaTeXState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [String] -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => [String] -> m ()
setResourcePath ([String] -> ParsecT TokStream LaTeXState m ())
-> ([String] -> [String])
-> [String]
-> ParsecT TokStream LaTeXState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
ps)
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
splitBibs :: Text -> [Inlines]
splitBibs :: Text -> [Inlines]
splitBibs = (Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Inlines
str (Text -> Inlines) -> (Text -> Text) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String -> String) -> String -> String -> String
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> String -> String
replaceExtension String
"bib" (String -> String) -> (Text -> String) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> String) -> (Text -> Text) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trim) ([Text] -> [Inlines]) -> (Text -> [Text]) -> Text -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
splitTextBy (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
',')
alltt :: Blocks -> Blocks
alltt :: Blocks -> Blocks
alltt = (Inline -> Inline) -> Blocks -> Blocks
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
strToCode
where strToCode :: Inline -> Inline
strToCode (Str Text
s) = Attr -> Text -> Inline
Code Attr
nullAttr Text
s
strToCode Inline
Space = Format -> Text -> Inline
RawInline (Text -> Format
Format Text
"latex") Text
"\\ "
strToCode Inline
SoftBreak = Inline
LineBreak
strToCode Inline
x = Inline
x
parseListingsOptions :: [(Text, Text)] -> Attr
parseListingsOptions :: [(Text, Text)] -> Attr
parseListingsOptions [(Text, Text)]
options =
let kvs :: [(Text, Text)]
kvs = [ (if Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"firstnumber"
then Text
"startFrom"
else Text
k, Text
v) | (Text
k,Text
v) <- [(Text, Text)]
options ]
classes :: [Text]
classes = [ Text
"numberLines" |
Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"numbers" [(Text, Text)]
options Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"left" ]
[Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ Maybe Text -> [Text]
forall a. Maybe a -> [a]
maybeToList ([(Text, Text)] -> Maybe Text
listingsLanguage [(Text, Text)]
options)
in (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"label" [(Text, Text)]
options), [Text]
classes, [(Text, Text)]
kvs)
inputListing :: PandocMonad m => LP m Blocks
inputListing :: forall (m :: * -> *). PandocMonad m => LP m Blocks
inputListing = do
SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
[(Text, Text)]
options <- [(Text, Text)]
-> ParsecT TokStream LaTeXState m [(Text, Text)]
-> ParsecT TokStream LaTeXState 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 TokStream LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
Text
f <- (Char -> Bool) -> Text -> Text
T.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'"') (Text -> Text) -> ([Tok] -> Text) -> [Tok] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Maybe Text
mbCode <- String -> LP m (Maybe Text)
forall (m :: * -> *). PandocMonad m => String -> LP m (Maybe Text)
readFileFromTexinputs (Text -> String
T.unpack Text
f)
[Text]
codeLines <- case Maybe Text
mbCode of
Just Text
s -> [Text] -> ParsecT TokStream LaTeXState m [Text]
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> ParsecT TokStream LaTeXState m [Text])
-> [Text] -> ParsecT TokStream LaTeXState m [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.lines Text
s
Maybe Text
Nothing -> do
LogMessage -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT TokStream LaTeXState m ())
-> LogMessage -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
CouldNotLoadIncludeFile Text
f SourcePos
pos
[Text] -> ParsecT TokStream LaTeXState m [Text]
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return []
let (Text
ident,[Text]
classes,[(Text, Text)]
kvs) = [(Text, Text)] -> Attr
parseListingsOptions [(Text, Text)]
options
let classes' :: [Text]
classes' =
(case [(Text, Text)] -> Maybe Text
listingsLanguage [(Text, Text)]
options of
Maybe Text
Nothing -> (Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
take Int
1 (SyntaxMap -> Text -> [Text]
languagesByExtension SyntaxMap
defaultSyntaxMap
(String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> String
takeExtension (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
f)) [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<>)
Just Text
_ -> [Text] -> [Text]
forall a. a -> a
id) [Text]
classes
let firstline :: Int
firstline = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"firstline" [(Text, Text)]
options Maybe Text -> (Text -> Maybe Int) -> Maybe Int
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead
let lastline :: Int
lastline = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe ([Text] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
codeLines) (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$
Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"lastline" [(Text, Text)]
options Maybe Text -> (Text -> Maybe Int) -> Maybe Int
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead
let codeContents :: Text
codeContents = Text -> [Text] -> Text
T.intercalate Text
"\n" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
take (Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lastline Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
firstline) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$
Int -> [Text] -> [Text]
forall a. Int -> [a] -> [a]
drop (Int
firstline Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [Text]
codeLines
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Blocks
codeBlockWith (Text
ident,[Text]
classes',[(Text, Text)]
kvs) Text
codeContents
item :: PandocMonad m => LP m Blocks
item :: forall (m :: * -> *). PandocMonad m => LP m Blocks
item = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m Tok
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> ParsecT TokStream LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"item" ParsecT TokStream LaTeXState m Tok
-> ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m ()
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
descItem :: PandocMonad m => LP m (Inlines, [Blocks])
descItem :: forall (m :: * -> *). PandocMonad m => LP m (Inlines, [Blocks])
descItem = do
ParsecT TokStream LaTeXState m ()
-> ParsecT TokStream LaTeXState m (Maybe ())
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"item"
ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp
Inlines
ils <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt
Blocks
bs <- LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
(Inlines, [Blocks]) -> LP m (Inlines, [Blocks])
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines
ils, [Blocks
bs])
listenv :: PandocMonad m => Text -> LP m a -> LP m a
listenv :: forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
listenv Text
name LP m a
p = LP m a -> LP m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (LP m a -> LP m a) -> LP m a -> LP m a
forall a b. (a -> b) -> a -> b
$ do
Bool
oldInListItem <- LaTeXState -> Bool
sInListItem (LaTeXState -> Bool)
-> ParsecT TokStream LaTeXState m LaTeXState
-> ParsecT TokStream LaTeXState m Bool
forall a b.
(a -> b)
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecT TokStream LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sInListItem = True }
a
res <- Text -> LP m a -> LP m a
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
name LP m a
p
(LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT TokStream LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sInListItem = oldInListItem }
a -> LP m a
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
res
orderedList' :: PandocMonad m => LP m Blocks
orderedList' :: forall (m :: * -> *). PandocMonad m => LP m Blocks
orderedList' = ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks)
-> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ do
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
let markerSpec :: ParsecT TokStream LaTeXState m ListAttributes
markerSpec = do
Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'['
Text
ts <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Tok -> LP m Tok -> ParsecT TokStream LaTeXState m [Tok]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Char -> LP m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
']')
case Parsec Text ParserState ListAttributes
-> ParserState
-> String
-> Text
-> Either ParseError ListAttributes
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
runParser Parsec Text ParserState ListAttributes
forall s (m :: * -> *).
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s ParserState m ListAttributes
anyOrderedListMarker ParserState
forall a. Default a => a
def String
"option" Text
ts of
Right ListAttributes
r -> ListAttributes -> ParsecT TokStream LaTeXState m ListAttributes
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ListAttributes
r
Left ParseError
_ -> do
SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
LogMessage -> LP m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> LP m ()) -> LogMessage -> LP m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent (Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ts Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]") SourcePos
pos
ListAttributes -> ParsecT TokStream LaTeXState m ListAttributes
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
1, ListNumberStyle
DefaultStyle, ListNumberDelim
DefaultDelim)
(Int
_, ListNumberStyle
style, ListNumberDelim
delim) <- ListAttributes
-> ParsecT TokStream LaTeXState m ListAttributes
-> ParsecT TokStream LaTeXState m ListAttributes
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Int
1, ListNumberStyle
DefaultStyle, ListNumberDelim
DefaultDelim) ParsecT TokStream LaTeXState m ListAttributes
markerSpec
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m (Maybe [Tok])
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m (Maybe [Tok]))
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m (Maybe [Tok])
forall a b. (a -> b) -> a -> b
$ ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok])
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b. (a -> b) -> a -> b
$ Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"setlength"
LP m Tok
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped (Int -> LP m Tok -> ParsecT TokStream LaTeXState m [Tok]
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
1 (LP m Tok -> ParsecT TokStream LaTeXState m [Tok])
-> LP m Tok -> ParsecT TokStream LaTeXState m [Tok]
forall a b. (a -> b) -> a -> b
$ Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"itemindent")
ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m [Tok]
forall a b.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
Int
start <- Int
-> ParsecT TokStream LaTeXState m Int
-> ParsecT TokStream LaTeXState m Int
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Int
1 (ParsecT TokStream LaTeXState m Int
-> ParsecT TokStream LaTeXState m Int)
-> ParsecT TokStream LaTeXState m Int
-> ParsecT TokStream LaTeXState m Int
forall a b. (a -> b) -> a -> b
$ ParsecT TokStream LaTeXState m Int
-> ParsecT TokStream LaTeXState m Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT TokStream LaTeXState m Int
-> ParsecT TokStream LaTeXState m Int)
-> ParsecT TokStream LaTeXState m Int
-> ParsecT TokStream LaTeXState m Int
forall a b. (a -> b) -> a -> b
$ do SourcePos
pos <- ParsecT TokStream LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"setcounter"
Text
ctr <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
Bool -> LP m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> LP m ()) -> Bool -> LP m ()
forall a b. (a -> b) -> a -> b
$ Text
"enum" Text -> Text -> Bool
`T.isPrefixOf` Text
ctr
Bool -> LP m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> LP m ()) -> Bool -> LP m ()
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Bool
T.all (Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'i',Char
'v']) (Int -> Text -> Text
T.drop Int
4 Text
ctr)
LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp
Text
num <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT TokStream LaTeXState m [Tok]
-> ParsecT TokStream LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
case Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead Text
num of
Just Int
i -> Int -> ParsecT TokStream LaTeXState m Int
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 :: Int)
Maybe Int
Nothing -> do
LogMessage -> LP m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> LP m ()) -> LogMessage -> LP m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent
(Text
"\\setcounter{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
ctr Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"}{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
num Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}") SourcePos
pos
Int -> ParsecT TokStream LaTeXState m Int
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
1
[Blocks]
bs <- Text -> LP m [Blocks] -> LP m [Blocks]
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
listenv Text
"enumerate" (ParsecT TokStream LaTeXState m Blocks -> LP m [Blocks]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
item)
Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> ParsecT TokStream LaTeXState m Blocks)
-> Blocks -> ParsecT TokStream LaTeXState m Blocks
forall a b. (a -> b) -> a -> b
$ ListAttributes -> [Blocks] -> Blocks
orderedListWith (Int
start, ListNumberStyle
style, ListNumberDelim
delim) [Blocks]
bs
block :: PandocMonad m => LP m Blocks
block :: forall (m :: * -> *). PandocMonad m => LP m Blocks
block = do
Tok SourcePos
_ TokType
toktype Text
_ <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
peekTok
Blocks
res <- (case TokType
toktype of
TokType
Newline -> Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1
TokType
Spaces -> Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1
TokType
Comment -> Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT TokStream LaTeXState m () -> LP m Blocks
forall a b.
a
-> ParsecT TokStream LaTeXState m b
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1
TokType
Word -> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
paragraph
CtrlSeq Text
"begin" -> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
environment
CtrlSeq Text
_ -> (Text -> Blocks) -> LP m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
(Text -> a) -> LP m a
macroDef (Text -> Text -> Blocks
rawBlock Text
"latex")
LP m Blocks -> LP m Blocks -> LP m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blockCommand
TokType
_ -> LP m Blocks
forall a. ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero)
LP m Blocks -> LP m Blocks -> LP m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
paragraph
LP m Blocks -> LP m Blocks -> LP m Blocks
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
Text -> ParsecT TokStream LaTeXState m ()
forall (m :: * -> *). PandocMonad m => Text -> m ()
trace (Int -> Text -> Text
T.take Int
60 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Block] -> Text
forall a. Show a => a -> Text
tshow ([Block] -> Text) -> [Block] -> Text
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
res)
Blocks -> LP m Blocks
forall a. a -> ParsecT TokStream LaTeXState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res
blocks :: PandocMonad m => LP m Blocks
blocks :: forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks = [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT TokStream LaTeXState m [Blocks]
-> ParsecT TokStream LaTeXState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT TokStream LaTeXState m Blocks
-> ParsecT TokStream LaTeXState m [Blocks]
forall a.
ParsecT TokStream LaTeXState m a
-> ParsecT TokStream LaTeXState m [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT TokStream LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block